filepath-1.4.99.0: Library for manipulating FilePaths in a cross platform way.
Safe HaskellNone
LanguageHaskell2010

System.OsString.Windows

Synopsis

Types

data WindowsString Source #

Commonly used windows string as UTF16 bytes.

Instances

Instances details
Eq WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Ord WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Show WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

showsPrec :: Int -> WindowsString -> ShowS

show :: WindowsString -> String

showList :: [WindowsString] -> ShowS

Generic WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep WindowsString :: Type -> Type

Semigroup WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Monoid WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

NFData WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: WindowsString -> ()

Lift WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

lift :: WindowsString -> Q Exp

liftTyped :: WindowsString -> Q (TExp WindowsString)

type Rep WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep WindowsString = D1 ('MetaData "WindowsString" "System.OsString.Internal.Types" "filepath-1.4.99.0-inplace" 'True) (C1 ('MetaCons "WindowsString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getWindowsString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))

data WindowsChar Source #

Instances

Instances details
Eq WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

(==) :: WindowsChar -> WindowsChar -> Bool

(/=) :: WindowsChar -> WindowsChar -> Bool

Ord WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Show WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

showsPrec :: Int -> WindowsChar -> ShowS

show :: WindowsChar -> String

showList :: [WindowsChar] -> ShowS

Generic WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep WindowsChar :: Type -> Type

Methods

from :: WindowsChar -> Rep WindowsChar x

to :: Rep WindowsChar x -> WindowsChar

NFData WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: WindowsChar -> ()

type Rep WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep WindowsChar = D1 ('MetaData "WindowsChar" "System.OsString.Internal.Types" "filepath-1.4.99.0-inplace" 'True) (C1 ('MetaCons "WindowsChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getWindowsChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)))

String construction

toPlatformStringUtf :: MonadThrow m => String -> m WindowsString Source #

Partial unicode friendly encoding.

This encodes as UTF16-LE (strictly), which is a pretty good guess.

Throws an EncodingException if encoding fails.

toPlatformStringEnc :: TextEncoding -> String -> Either EncodingException WindowsString Source #

Like toPlatformStringUtf, except allows to provide an encoding.

toPlatformStringFS :: String -> IO WindowsString Source #

Like toPlatformStringUtf, except this mimics the behavior of the base library when doing filesystem operations, which does permissive UTF-16 encoding, where coding errors generate Chars in the surrogate range.

The reason this is in IO is because it unifies with the Posix counterpart, which does require IO. This is safe to unsafePerformIO/unsafeDupablePerformIO.

bytesToPlatformString :: MonadThrow m => ByteString -> m WindowsString Source #

Constructs a platform string from a ByteString.

This ensures valid UCS-2LE. Note that this doesn't expand Word8 to Word16 on windows, so you may get invalid UTF-16.

Throws EncodingException on invalid UCS-2LE (although unlikely).

pstr :: QuasiQuoter Source #

QuasiQuote a WindowsString. This accepts Unicode characters and encodes as UTF-16 on windows.

packPlatformString :: [WindowsChar] -> WindowsString Source #

Pack a list of platform words to a platform string.

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

String deconstruction

fromPlatformStringUtf :: MonadThrow m => WindowsString -> m String Source #

Partial unicode friendly decoding.

This decodes as UTF16-LE (strictly), which is a pretty good.

Throws a EncodingException if decoding fails.

fromPlatformStringEnc :: TextEncoding -> WindowsString -> Either EncodingException String Source #

Like fromPlatformStringUtf, except allows to provide a text encoding.

The String is forced into memory to catch all exceptions.

fromPlatformStringFS :: WindowsString -> IO String Source #

Like fromPlatformStringUtf, except this mimics the behavior of the base library when doing filesystem operations, which does permissive UTF-16 encoding, where coding errors generate Chars in the surrogate range.

The reason this is in IO is because it unifies with the Posix counterpart, which does require IO. unsafePerformIO/unsafeDupablePerformIO are safe, however.

unpackPlatformString :: WindowsString -> [WindowsChar] Source #

Unpack a platform string to a list of platform words.

Word construction

unsafeFromChar :: Char -> WindowsChar Source #

Truncates to 2 octets.

Word deconstruction

toChar :: WindowsChar -> Char Source #

Converts back to a unicode codepoint (total).