Win32-2.14.1.0: A binding to Windows Win32 API.
Copyright(c) Alastair Reid 1999-2003
LicenseBSD-style (see the file libraries/base/LICENSE)
MaintainerEsa Ilari Vuokko <ei@vuokko.info>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

System.Win32

Description

An FFI binding to the system part of the Win32 API.

Synopsis

Documentation

type CodePage = DWORD #

data GUID Source #

Constructors

GUID !Word32 !Word16 !Word16 !Word8 !Word8 !Word8 !Word8 !Word8 !Word8 !Word8 !Word8 

Instances

Instances details
Eq GUID Source # 
Instance details

Defined in System.Win32.NLS

Methods

(==) :: GUID -> GUID -> Bool

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

Show GUID Source # 
Instance details

Defined in System.Win32.NLS

Methods

showsPrec :: Int -> GUID -> ShowS

show :: GUID -> String

showList :: [GUID] -> ShowS

Storable GUID Source # 
Instance details

Defined in System.Win32.NLS

Methods

sizeOf :: GUID -> Int

alignment :: GUID -> Int

peekElemOff :: Ptr GUID -> Int -> IO GUID

pokeElemOff :: Ptr GUID -> Int -> GUID -> IO ()

peekByteOff :: Ptr b -> Int -> IO GUID

pokeByteOff :: Ptr b -> Int -> GUID -> IO ()

peek :: Ptr GUID -> IO GUID

poke :: Ptr GUID -> GUID -> IO ()

data NLSVERSIONINFOEX Source #

Instances

Instances details
Eq NLSVERSIONINFOEX Source # 
Instance details

Defined in System.Win32.NLS

Show NLSVERSIONINFOEX Source # 
Instance details

Defined in System.Win32.NLS

Methods

showsPrec :: Int -> NLSVERSIONINFOEX -> ShowS

show :: NLSVERSIONINFOEX -> String

showList :: [NLSVERSIONINFOEX] -> ShowS

Storable NLSVERSIONINFOEX Source # 
Instance details

Defined in System.Win32.NLS

data LOCALESIGNATURE Source #

Instances

Instances details
Eq LOCALESIGNATURE Source # 
Instance details

Defined in System.Win32.NLS

Show LOCALESIGNATURE Source # 
Instance details

Defined in System.Win32.NLS

Methods

showsPrec :: Int -> LOCALESIGNATURE -> ShowS

show :: LOCALESIGNATURE -> String

showList :: [LOCALESIGNATURE] -> ShowS

Storable LOCALESIGNATURE Source # 
Instance details

Defined in System.Win32.NLS

Methods

sizeOf :: LOCALESIGNATURE -> Int

alignment :: LOCALESIGNATURE -> Int

peekElemOff :: Ptr LOCALESIGNATURE -> Int -> IO LOCALESIGNATURE

pokeElemOff :: Ptr LOCALESIGNATURE -> Int -> LOCALESIGNATURE -> IO ()

peekByteOff :: Ptr b -> Int -> IO LOCALESIGNATURE

pokeByteOff :: Ptr b -> Int -> LOCALESIGNATURE -> IO ()

peek :: Ptr LOCALESIGNATURE -> IO LOCALESIGNATURE

poke :: Ptr LOCALESIGNATURE -> LOCALESIGNATURE -> IO ()

data LCData Source #

Constructors

LCTextualData !String

Data in the form of a Unicode string.

LCNumericData !DWORD

Data in the form of a number. See lOCAL_RETURN_NUMBER and LOCAL_I* locate information constants.

LCSignatureData !LOCALESIGNATURE

Data in the fomr of a LOCALESIGNATURE. See lOCAL_FONTSIGNATURE locale information constant.

Instances

Instances details
Eq LCData Source # 
Instance details

Defined in System.Win32.NLS

Methods

(==) :: LCData -> LCData -> Bool

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

Show LCData Source # 
Instance details

Defined in System.Win32.NLS

Methods

showsPrec :: Int -> LCData -> ShowS

show :: LCData -> String

showList :: [LCData] -> ShowS

multiByteToWideChar :: CodePage -> DWORD -> LPCSTR -> CInt -> LPWSTR -> CInt -> IO CInt Source #

c_LCMapString :: LCID -> LCMapFlags -> LPCTSTR -> Int -> LPCTSTR -> Int -> IO Int Source #

c_LCMapStringEx :: LPCWSTR -> LCMapFlags -> LPCWSTR -> CInt -> LPWSTR -> CInt -> Ptr NLSVERSIONINFOEX -> LPVOID -> LPARAM -> IO CInt Source #

c_GetLocaleInfoEx :: LPCWSTR -> LCTYPE -> LPWSTR -> CInt -> IO CInt Source #

lOCALE_SDATE :: LCTYPE Source #

Type representing locale data

lOCALE_SISO3166CTRYNAME2 :: LCTYPE Source #

Type representing 128-bit Unicode subset bitfields, as the base package does include a module exporting a 128-bit unsigned integer type.

getLocaleInfoEx :: Maybe String -> LCTYPE -> IO LCData Source #

setLocaleInfo :: LCID -> LCTYPE -> String -> IO () Source #

lCMapStringEx :: Maybe String -> LCMapFlags -> String -> NLSVERSIONINFOEX -> IO String Source #

lCMapString :: LCID -> LCMapFlags -> String -> Int -> IO String Source #

isValidLocaleName :: Maybe String -> IO Bool Source #

enumSystemLocalesEx' Source #

Arguments

:: EnumLocalesFlag 
-> Maybe Bool

Maybe include (or exclude) replacement locales?

-> IO [String] 

getDefaultLocaleName :: String -> (LPWSTR -> CInt -> IO CInt) -> IO String Source #

Helper function for use with c_GetUserDefaultLocaleName or c_GetSystemDefaultLocaleName. See getUserDefaultLocaleName and getSystemUserDefaultLocaleName.

sUBLANG_ENGLISH_SOUTH_AFRICA :: SubLANGID Source #

The IO input functions (e.g., getLine) don't automatically convert to Unicode, so this function is provided to make the conversion from a multibyte string in the given code page to a proper Unicode string. To get the code page for the console, use getConsoleCP.

stringToUnicode :: CodePage -> String -> IO String Source #

maybePtr :: Maybe (Ptr a) -> Ptr a Source #

ptrToMaybe :: Ptr a -> Maybe (Ptr a) Source #

maybeNum :: Num a => Maybe a -> a Source #

numToMaybe :: (Eq a, Num a) => a -> Maybe a Source #

tryWithoutNull :: String -> (LPTSTR -> UINT -> IO UINT) -> UINT -> IO String Source #

try' :: Storable a => String -> (Ptr a -> PDWORD -> IO BOOL) -> DWORD -> IO [a] Source #

trySized :: String -> (LPTSTR -> CInt -> IO CInt) -> IO String Source #

Support for API calls that return the required size, in characters including a null character, of the buffer when passed a buffer size of zero.

peekMaybe :: Storable a => Ptr a -> IO (Maybe a) Source #

See also: maybePeek function.

withMaybe :: Storable a => Maybe a -> (Ptr a -> IO b) -> IO b Source #

See also: maybeWith function.

fromDateFormatPicture :: String -> Maybe String Source #

Translate from a Windows API day, month, year, and era format picture to the closest corresponding format string used by formatTime.

fromTimeFormatPicture :: String -> Maybe String Source #

Translate from a Windows API hours, minute, and second format picture to the closest corresponding format string used by formatTime.