Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- toAbstractFilePathUtf :: MonadThrow m => String -> m AbstractFilePath
- toAbstractFilePathEnc :: TextEncoding -> TextEncoding -> String -> Either EncodingException AbstractFilePath
- toAbstractFilePathFS :: String -> IO AbstractFilePath
- fromAbstractFilePathUtf :: MonadThrow m => AbstractFilePath -> m String
- fromAbstractFilePathEnc :: TextEncoding -> TextEncoding -> AbstractFilePath -> Either EncodingException String
- fromAbstractFilePathFS :: AbstractFilePath -> IO String
- bytesToAFP :: MonadThrow m => ByteString -> m AbstractFilePath
- mkAbstractFilePath :: ByteString -> Q Exp
- afp :: QuasiQuoter
- unpackAFP :: AbstractFilePath -> [OsChar]
- packAFP :: [OsChar] -> AbstractFilePath
Documentation
toAbstractFilePathUtf :: MonadThrow m => String -> m AbstractFilePath Source #
Convert a String.
On windows this encodes as UTF16, which is a pretty good guess. On unix this encodes as UTF8, which is a good guess.
Throws a EncodingException
if encoding fails.
toAbstractFilePathEnc Source #
:: TextEncoding | unix text encoding |
-> TextEncoding | windows text encoding |
-> String | |
-> Either EncodingException AbstractFilePath |
Like toAbstractFilePathUtf
, except allows to provide encodings.
toAbstractFilePathFS :: String -> IO AbstractFilePath Source #
Like toAbstractFilePathUtf
, except on unix this uses the current
filesystem 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 (make sure
to deeply evaluate the result to catch exceptions).
Throws EncodingException
if decoding fails.
fromAbstractFilePathUtf :: MonadThrow m => AbstractFilePath -> m String Source #
Partial unicode friendly decoding.
On windows this decodes as UTF16-LE (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 EncodingException
if decoding fails.
Note that filenames of different encodings may have the same String
representation, although they're not the same byte-wise.
fromAbstractFilePathEnc Source #
:: TextEncoding | unix text encoding |
-> TextEncoding | windows text encoding |
-> AbstractFilePath | |
-> Either EncodingException String |
Like fromAbstractFilePathUtf
, except on unix this uses the provided
TextEncoding
for decoding.
On windows, the TextEncoding parameter is ignored.
fromAbstractFilePathFS :: AbstractFilePath -> IO String Source #
Like fromAbstractFilePathUtf
, except on unix this uses the current
locale for decoding instead of always UTF8. On windows, uses UTF-16LE.
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).
Throws EncodingException
if decoding fails.
bytesToAFP :: MonadThrow m => ByteString -> m AbstractFilePath Source #
Constructs an AbstractFilePath
from a ByteString.
On windows, this ensures valid UCS-2LE, on unix it is passed unchanged/unchecked.
Throws EncodingException
on invalid UCS-2LE on windows (although unlikely).
mkAbstractFilePath :: ByteString -> Q Exp Source #
QuasiQuote an AbstractFilePath
. This accepts Unicode characters
and encodes as UTF-8 on unix and UTF-16 on windows. Runs filepathIsValid
on the input.
packAFP :: [OsChar] -> AbstractFilePath Source #
Pack a list of OsChar
to an AbstractFilePath
.
Note that using this in conjunction with unsafeFromChar
to
convert from [Char]
to AbstractFilePath
is probably not what
you want, because it will truncate unicode code points.