filepath-2.0.0.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

Read WindowsString Source #

Encodes as UTF-16LE.

Instance details

Defined in System.OsString.Internal.Types

Show WindowsString Source #

Decodes as UTF-16LE.

Instance details

Defined in System.OsString.Internal.Types

IsString WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

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

type Rep WindowsString Source # 
Instance details

Defined in System.OsString.Internal.Types

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

data WindowsChar Source #

Instances

Instances details
Eq WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Ord WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Show WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Generic WindowsChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep WindowsChar :: Type -> Type #

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-2.0.0.0-inplace" 'True) (C1 ('MetaCons "WW" 'PrefixI 'True) (S1 ('MetaSel ('Just "unWW") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)))

String construction

toPlatformString :: String -> WindowsString 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.

toPlatformStringIO :: String -> IO WindowsString Source #

Like toPlatformString, 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.

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

Constructs an platform string from a ByteString.

On windows, this ensures valid UTF16, on unix it is passed unchanged/unchecked.

Throws UnicodeException on invalid UTF16 on windows.

pstr :: QuasiQuoter Source #

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

String deconstruction

fromPlatformString :: MonadThrow m => WindowsString -> 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.

fromPlatformStringIO :: WindowsString -> IO String Source #

Like fromPlatformString, 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.

Word construction

unsafeFromChar :: Char -> WindowsChar Source #

Truncates to 2 octets.

Word deconstruction

toChar :: WindowsChar -> Char Source #

Converts back to a unicode codepoint (total).