Copyright | © 2021 Julian Ospald |
---|---|
License | MIT |
Maintainer | Julian Ospald <hasufell@posteo.de> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
An implementation of platform specific short OsString
, which is:
- on windows UTF16 data
- 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
- data OsString
- toOsString :: String -> OsString
- toOsStringIO :: String -> IO OsString
- bsToOsString :: MonadThrow m => ByteString -> m OsString
- osstr :: QuasiQuoter
- packOsString :: [OsChar] -> OsString
- fromOsString :: MonadThrow m => OsString -> m String
- fromOsStringEnc :: OsString -> TextEncoding -> Either UnicodeException String
- fromOsStringIO :: OsString -> IO String
- unpackOsString :: 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
Eq OsString Source # | Byte equality of the internal representation. |
Ord OsString Source # | Byte ordering of the internal representation. |
Defined in System.OsString.Internal.Types | |
Read OsString Source # | Encodes as UTF-8 on unix and UTF-16LE on windows. |
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. |
IsString OsString Source # | Encodes as UTF16 on windows and UTF8 on unix. |
Defined in System.OsString.Internal.Types fromString :: String -> OsString # | |
Generic OsString Source # | |
Semigroup OsString Source # | |
Monoid OsString Source # | "String-Concatenation" for 'OsString. This is not the same
as |
NFData OsString Source # | |
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-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.
packOsString :: [OsChar] -> OsString Source #
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.
unpackOsString :: OsString -> [OsChar] Source #
Word types
Newtype representing a code unit.
On Windows, this is restricted to two-octet codepoints Word16
,
on POSIX one-octet (Word8
).
Instances
Eq OsChar Source # | Byte equality of the internal representation. |
Ord OsChar Source # | Byte ordering of the internal representation. |
Show OsChar Source # | |
Generic OsChar Source # | |
NFData OsChar Source # | |
Defined in System.OsString.Internal.Types | |
type Rep OsChar Source # | |
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.