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

System.OsString.Posix

Description

Deprecated: Use System.OsString.Posix from os-string >= 2.0.0 package instead. This module will be removed in filepath >= 1.5.

Synopsis

Documentation

toChar :: PosixChar -> Char Source #

Converts back to a unicode codepoint (total).

pack :: [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.

unpack :: PosixString -> [PosixChar] Source #

Unpack a platform string to a list of platform words.

unsafeFromChar :: Char -> PosixChar Source #

Truncates to 1 octet.

encodeUtf :: MonadThrow m => String -> m PosixString Source #

Partial unicode friendly encoding.

This encodes as UTF8 (strictly), which is a good guess.

Throws an EncodingException if encoding fails.

encodeWith :: TextEncoding -> String -> Either EncodingException PosixString Source #

Encode a String with the specified encoding.

encodeFS :: String -> IO PosixString Source #

This mimics the behavior of the base library when doing filesystem operations, which uses shady PEP 383 style encoding (based on the current locale, but PEP 383 only works properly on UTF-8 encodings, so good luck).

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

decodeUtf :: MonadThrow m => PosixString -> m String Source #

Partial unicode friendly decoding.

This decodes as UTF8 (strictly), which is a good guess. Note that filenames on unix are encoding agnostic char arrays.

Throws a EncodingException if decoding fails.

decodeWith :: TextEncoding -> PosixString -> Either EncodingException String Source #

Decode a PosixString with the specified encoding.

The String is forced into memory to catch all exceptions.

decodeFS :: PosixString -> IO String Source #

This mimics the behavior of the base library when doing filesystem operations, which uses shady PEP 383 style encoding (based on the current locale, but PEP 383 only works properly on UTF-8 encodings, so good luck).

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

data PosixString Source #

Commonly used Posix string as uninterpreted char[] array.

Instances

Instances details
Monoid PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Semigroup PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Generic PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep PosixString = D1 ('MetaData "PosixString" "System.OsString.Internal.Types.Hidden" "filepath-1.4.200.1-2a10" 'True) (C1 ('MetaCons "PosixString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))
Show PosixString Source #

Prints the raw bytes without decoding.

Instance details

Defined in System.OsString.Internal.Types.Hidden

NFData PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

rnf :: PosixString -> () Source #

Eq PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Ord PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Lift PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

lift :: Quote m => PosixString -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => PosixString -> Code m PosixString Source #

type Rep PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep PosixString = D1 ('MetaData "PosixString" "System.OsString.Internal.Types.Hidden" "filepath-1.4.200.1-2a10" 'True) (C1 ('MetaCons "PosixString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))

data PosixChar Source #

Instances

Instances details
Generic PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep PosixChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep PosixChar = D1 ('MetaData "PosixChar" "System.OsString.Internal.Types.Hidden" "filepath-1.4.200.1-2a10" 'True) (C1 ('MetaCons "PosixChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)))
Show PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types.Hidden

NFData PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

rnf :: PosixChar -> () Source #

Eq PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Ord PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep PosixChar = D1 ('MetaData "PosixChar" "System.OsString.Internal.Types.Hidden" "filepath-1.4.200.1-2a10" 'True) (C1 ('MetaCons "PosixChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)))

pstr :: QuasiQuoter Source #

QuasiQuote a PosixString. This accepts Unicode characters and encodes as UTF-8 on unix.

fromBytes :: MonadThrow m => ByteString -> m PosixString Source #

Constructs a platform string from a ByteString.

This is a no-op.