filepath-2.0.0.0: Library for manipulating FilePaths in a cross platform way.
Copyright© 2021 Julian Ospald
LicenseMIT
MaintainerJulian Ospald <hasufell@posteo.de>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

System.OsString

Description

An implementation of platform specific short OsString, which is:

  1. on windows UTF16 data
  2. on unix UTF8 data

It captures the notion of syscall specific encoding to avoid roundtrip issues and memory fragmentation by using unpinned byte arrays.

Synopsis

String types

data OsString Source #

Newtype representing short operating system specific strings.

Internally this is either WindowsString or PosixString, depending on the platform. Both use unpinned ShortByteString for efficiency.

The constructor is only exported via System.OsString.Internal.Types, since dealing with the internals isn't generally recommended, but supported in case you need to write platform specific code.

Instances

Instances details
Eq OsString Source #

Byte equality of the internal representation.

Instance details

Defined in System.OsString.Internal.Types

Ord OsString Source #

Byte ordering of the internal representation.

Instance details

Defined in System.OsString.Internal.Types

Read OsString Source #

Encodes as UTF-8 on unix and UTF-16LE on windows.

Instance details

Defined in System.OsString.Internal.Types

Show OsString Source #

Decodes as UTF-16 on windows.

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

Instance details

Defined in System.OsString.Internal.Types

IsString OsString Source #

Encodes as UTF16 on windows and UTF8 on unix.

Instance details

Defined in System.OsString.Internal.Types

Generic OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep OsString :: Type -> Type #

Methods

from :: OsString -> Rep OsString x #

to :: Rep OsString x -> OsString #

Semigroup OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Monoid OsString Source #

"String-Concatenation" for 'OsString. This is not the same as (</>).

Instance details

Defined in System.OsString.Internal.Types

NFData OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: OsString -> () #

Lift OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep OsString = D1 ('MetaData "OsString" "System.OsString.Internal.Types" "filepath-2.0.0.0-inplace" 'True) (C1 ('MetaCons "OsString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformString)))

String construction

toOsString :: String -> OsString Source #

Total Unicode-friendly encoding.

On windows this encodes as UTF16, which is expected. On unix this encodes as UTF8, which is a good guess.

toOsStringIO :: String -> IO OsString Source #

Like toOsString, except on unix this uses the current 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.

bsToOsString :: MonadThrow m => ByteString -> m OsString Source #

Constructs an OsString from a ByteString.

On windows, this ensures valid UTF16, on unix it is passed unchanged/unchecked.

Throws UnicodeException on invalid UTF16 on windows.

osstr :: QuasiQuoter Source #

QuasiQuote an OsString. This accepts Unicode characters and encodes as UTF-8 on unix and UTF-16 on windows.

String deconstruction

fromOsString :: MonadThrow m => OsString -> m String Source #

Partial unicode friendly decoding.

On windows this decodes as UTF16 (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 UnicodeException if decoding fails.

fromOsStringEnc :: OsString -> TextEncoding -> Either UnicodeException String Source #

Like fromOsString, except on unix this uses the provided TextEncoding for decoding.

On windows, the TextEncoding parameter is ignored.

fromOsStringIO :: OsString -> IO String Source #

Like fromOsString, except on unix this uses the current locale for decoding instead of always UTF8.

Looking up the locale requires IO. If you're not worried about calls to setFileSystemEncoding, then unsafePerformIO may be feasible.

Throws UnicodeException if decoding fails.

Word types

data OsChar Source #

Newtype representing a code unit.

On Windows, this is restricted to two-octet codepoints Word16, on POSIX one-octet (Word8).

Instances

Instances details
Eq OsChar Source #

Byte equality of the internal representation.

Instance details

Defined in System.OsString.Internal.Types

Methods

(==) :: OsChar -> OsChar -> Bool #

(/=) :: OsChar -> OsChar -> Bool #

Ord OsChar Source #

Byte ordering of the internal representation.

Instance details

Defined in System.OsString.Internal.Types

Show OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Generic OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep OsChar :: Type -> Type #

Methods

from :: OsChar -> Rep OsChar x #

to :: Rep OsChar x -> OsChar #

NFData OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: OsChar -> () #

type Rep OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep OsChar = D1 ('MetaData "OsChar" "System.OsString.Internal.Types" "filepath-2.0.0.0-inplace" 'True) (C1 ('MetaCons "OsChar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformChar)))

Word construction

unsafeFromChar :: Char -> OsChar Source #

Truncates on unix to 1 and on Windows to 2 octets.

Word deconstruction

toChar :: OsChar -> Char Source #

Converts back to a unicode codepoint (total).