Copyright | © 2021 Julian Ospald |
---|---|
License | MIT |
Maintainer | Julian Ospald <hasufell@posteo.de> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
An implementation of platform specific short OsString
, which is:
- on windows wide char bytes (
[Word16]
) - 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
- data OsString
- encodeUtf :: MonadThrow m => String -> m OsString
- encodeWith :: TextEncoding -> TextEncoding -> String -> Either EncodingException OsString
- encodeFS :: String -> IO OsString
- osstr :: QuasiQuoter
- pack :: [OsChar] -> OsString
- decodeUtf :: MonadThrow m => OsString -> m String
- decodeWith :: TextEncoding -> TextEncoding -> OsString -> Either EncodingException String
- decodeFS :: OsString -> IO String
- unpack :: OsString -> [OsChar]
- data OsChar
- unsafeFromChar :: Char -> OsChar
- toChar :: OsChar -> Char
String types
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
Monoid OsString Source # | "String-Concatenation" for |
Semigroup OsString Source # | |
Generic OsString Source # | |
Show OsString Source # | On windows, decodes as UCS-2. On unix prints the raw bytes without decoding. |
NFData OsString Source # | |
Defined in System.OsString.Internal.Types | |
Eq OsString Source # | Byte equality of the internal representation. |
Ord OsString Source # | Byte ordering of the internal representation. |
Defined in System.OsString.Internal.Types | |
Lift OsString Source # | |
type Rep OsString Source # | |
Defined in System.OsString.Internal.Types type Rep OsString = D1 ('MetaData "OsString" "System.OsString.Internal.Types" "filepath-1.4.100.4-2ou6v9Oza7x86l4jie19Fo" '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.
:: 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:
- 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)
- 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.
:: 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:
- 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)
- 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).
Word types
Newtype representing a code unit.
On Windows, this is restricted to two-octet codepoints Word16
,
on POSIX one-octet (Word8
).
Instances
Generic OsChar Source # | |
Show OsChar Source # | |
NFData OsChar Source # | |
Defined in System.OsString.Internal.Types | |
Eq OsChar Source # | Byte equality of the internal representation. |
Ord OsChar Source # | Byte ordering of the internal representation. |
type Rep OsChar Source # | |
Defined in System.OsString.Internal.Types type Rep OsChar = D1 ('MetaData "OsChar" "System.OsString.Internal.Types" "filepath-1.4.100.4-2ou6v9Oza7x86l4jie19Fo" '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.