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

System.OsString

Description

An implementation of platform specific short OsString, which is:

  1. on windows wide char bytes ([Word16])
  2. on unix char bytes ([Word8])

It captures the notion of syscall specific encoding (or the lack thereof) to avoid roundtrip issues and memory fragmentation by using unpinned byte arrays. Bytes are not touched or interpreted.

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
Monoid OsString Source #

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

Instance details

Defined in System.OsString.Internal.Types

Semigroup OsString Source # 
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 Source #

Show OsString Source #

On windows, decodes as UCS-2. On unix prints the raw bytes without decoding.

Instance details

Defined in System.OsString.Internal.Types

NFData OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: OsString -> () Source #

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

Lift OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

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

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

type Rep OsString Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep OsString = D1 ('MetaData "OsString" "System.OsString.Internal.Types" "filepath-1.4.100.0" 'True) (C1 ('MetaCons "OsString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOsString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformString)))

OsString construction

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

Partial unicode friendly encoding.

On windows this encodes as UTF16-LE (strictly), which is a pretty good guess. On unix this encodes as UTF8 (strictly), which is a good guess.

Throws a EncodingException if encoding fails.

encodeWith Source #

Arguments

:: TextEncoding

unix text encoding

-> TextEncoding

windows text encoding

-> String 
-> Either EncodingException OsString 

Encode an OsString given the platform specific encodings.

encodeFS :: String -> IO OsString Source #

Like encodeUtf, except this mimics the behavior of the base library when doing filesystem operations, which is:

  1. on unix, uses shady PEP 383 style encoding (based on the current locale, but PEP 383 only works properly on UTF-8 encodings, so good luck)
  2. on windows does permissive UTF-16 encoding, where coding errors generate Chars in the surrogate range

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

osstr :: QuasiQuoter Source #

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

pack :: [OsChar] -> OsString Source #

Pack a list of OsChar to an OsString

Note that using this in conjunction with unsafeFromChar to convert from [Char] to OsString is probably not what you want, because it will truncate unicode code points.

OsString deconstruction

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

Partial unicode friendly decoding.

On windows this decodes as UTF16-LE (strictly), which is a pretty good guess. On unix 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 Source #

Arguments

:: TextEncoding

unix text encoding

-> TextEncoding

windows text encoding

-> OsString 
-> Either EncodingException String 

Decode an OsString with the specified encoding.

The String is forced into memory to catch all exceptions.

decodeFS :: OsString -> IO String Source #

Like decodeUtf, except this mimics the behavior of the base library when doing filesystem operations, which is:

  1. on unix, uses shady PEP 383 style encoding (based on the current locale, but PEP 383 only works properly on UTF-8 encodings, so good luck)
  2. on windows does permissive UTF-16 encoding, where coding errors generate Chars in the surrogate range

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

unpack :: OsString -> [OsChar] Source #

Unpack an OsString to a list of OsChar.

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
Generic OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep OsChar :: Type -> Type Source #

Show OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

NFData OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: OsChar -> () Source #

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

type Rep OsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep OsChar = D1 ('MetaData "OsChar" "System.OsString.Internal.Types" "filepath-1.4.100.0" 'True) (C1 ('MetaCons "OsChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOsChar") '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).