module Graphics.XHB.Gen.Xproto
       (createWindow, changeWindowAttributes, getWindowAttributes,
        destroyWindow, destroySubwindows, changeSaveSet, reparentWindow,
        mapWindow, mapSubwindows, unmapWindow, unmapSubwindows,
        configureWindow, circulateWindow, getGeometry, queryTree,
        internAtom, getAtomName, changeProperty, deleteProperty,
        getProperty, listProperties, setSelectionOwner, getSelectionOwner,
        convertSelection, sendEvent, grabPointer, ungrabPointer,
        grabButton, ungrabButton, changeActivePointerGrab, grabKeyboard,
        ungrabKeyboard, grabKey, ungrabKey, allowEvents, queryPointer,
        getMotionEvents, translateCoordinates, warpPointer, setInputFocus,
        getInputFocus, queryKeymap, openFont, closeFont, queryFont,
        queryTextExtents, listFonts, listFontsWithInfo, setFontPath,
        getFontPath, createPixmap, freePixmap, createGC, changeGC, copyGC,
        setDashes, setClipRectangles, freeGC, clearArea, copyArea,
        copyPlane, polyPoint, polyLine, polySegment, polyRectangle,
        polyArc, fillPoly, polyFillRectangle, polyFillArc, putImage,
        getImage, polyText8, polyText16, imageText8, imageText16,
        createColormap, freeColormap, copyColormapAndFree, installColormap,
        uninstallColormap, listInstalledColormaps, allocColor,
        allocNamedColor, allocColorCells, allocColorPlanes, freeColors,
        storeColors, storeNamedColor, queryColors, lookupColor,
        createCursor, createGlyphCursor, freeCursor, recolorCursor,
        queryBestSize, queryExtension, listExtensions,
        changeKeyboardMapping, getKeyboardMapping, changeKeyboardControl,
        getKeyboardControl, bell, changePointerControl, getPointerControl,
        setScreenSaver, getScreenSaver, changeHosts, listHosts,
        setAccessControl, setCloseDownMode, killClient, rotateProperties,
        forceScreenSaver, setPointerMapping, getPointerMapping,
        setModifierMapping, getModifierMapping,
        module Graphics.XHB.Gen.Xproto.Types)
       where
import Graphics.XHB.Gen.Xproto.Types
import Graphics.XHB.Connection.Internal
import Graphics.XHB.Shared
import Data.Binary.Put
import Control.Concurrent.STM
import Foreign.C.Types
import Data.Word
import Data.Int
import Data.Binary.Get
import qualified Graphics.XHB.Connection.Types
 
createWindow ::
               Graphics.XHB.Connection.Types.Connection -> CreateWindow -> IO ()
createWindow c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
changeWindowAttributes ::
                         Graphics.XHB.Connection.Types.Connection ->
                           WINDOW -> ValueParam Word32 -> IO ()
changeWindowAttributes c window value
  = do let req = MkChangeWindowAttributes window value
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
getWindowAttributes ::
                      Graphics.XHB.Connection.Types.Connection ->
                        WINDOW -> IO (Receipt GetWindowAttributesReply)
getWindowAttributes c window
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkGetWindowAttributes window
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
destroyWindow ::
                Graphics.XHB.Connection.Types.Connection -> WINDOW -> IO ()
destroyWindow c window
  = do let req = MkDestroyWindow window
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
destroySubwindows ::
                    Graphics.XHB.Connection.Types.Connection -> WINDOW -> IO ()
destroySubwindows c window
  = do let req = MkDestroySubwindows window
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
changeSaveSet ::
                Graphics.XHB.Connection.Types.Connection ->
                  SetMode -> WINDOW -> IO ()
changeSaveSet c mode window
  = do let req = MkChangeSaveSet mode window
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
reparentWindow ::
                 Graphics.XHB.Connection.Types.Connection -> ReparentWindow -> IO ()
reparentWindow c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
mapWindow ::
            Graphics.XHB.Connection.Types.Connection -> WINDOW -> IO ()
mapWindow c window
  = do let req = MkMapWindow window
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
mapSubwindows ::
                Graphics.XHB.Connection.Types.Connection -> WINDOW -> IO ()
mapSubwindows c window
  = do let req = MkMapSubwindows window
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
unmapWindow ::
              Graphics.XHB.Connection.Types.Connection -> WINDOW -> IO ()
unmapWindow c window
  = do let req = MkUnmapWindow window
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
unmapSubwindows ::
                  Graphics.XHB.Connection.Types.Connection -> WINDOW -> IO ()
unmapSubwindows c window
  = do let req = MkUnmapSubwindows window
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
configureWindow ::
                  Graphics.XHB.Connection.Types.Connection ->
                    WINDOW -> ValueParam Word16 -> IO ()
configureWindow c window value
  = do let req = MkConfigureWindow window value
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
circulateWindow ::
                  Graphics.XHB.Connection.Types.Connection ->
                    Circulate -> WINDOW -> IO ()
circulateWindow c direction window
  = do let req = MkCirculateWindow direction window
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
getGeometry ::
              Graphics.XHB.Connection.Types.Connection ->
                DRAWABLE -> IO (Receipt GetGeometryReply)
getGeometry c drawable
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkGetGeometry drawable
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
queryTree ::
            Graphics.XHB.Connection.Types.Connection ->
              WINDOW -> IO (Receipt QueryTreeReply)
queryTree c window
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkQueryTree window
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
internAtom ::
             Graphics.XHB.Connection.Types.Connection ->
               InternAtom -> IO (Receipt ATOM)
internAtom c req
  = do (receipt, rReceipt) <- newEmptyReceipt
                                (runGet (atom_InternAtomReply `fmap` deserialize))
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
getAtomName ::
              Graphics.XHB.Connection.Types.Connection ->
                ATOM -> IO (Receipt GetAtomNameReply)
getAtomName c atom
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkGetAtomName atom
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
changeProperty ::
                 Graphics.XHB.Connection.Types.Connection -> ChangeProperty -> IO ()
changeProperty c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
deleteProperty ::
                 Graphics.XHB.Connection.Types.Connection -> WINDOW -> ATOM -> IO ()
deleteProperty c window property
  = do let req = MkDeleteProperty window property
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
getProperty ::
              Graphics.XHB.Connection.Types.Connection ->
                GetProperty -> IO (Receipt GetPropertyReply)
getProperty c req
  = do (receipt, rReceipt) <- newDeserReceipt
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
listProperties ::
                 Graphics.XHB.Connection.Types.Connection ->
                   WINDOW -> IO (Receipt ListPropertiesReply)
listProperties c window
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkListProperties window
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
setSelectionOwner ::
                    Graphics.XHB.Connection.Types.Connection ->
                      SetSelectionOwner -> IO ()
setSelectionOwner c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
getSelectionOwner ::
                    Graphics.XHB.Connection.Types.Connection ->
                      ATOM -> IO (Receipt WINDOW)
getSelectionOwner c selection
  = do (receipt, rReceipt) <- newEmptyReceipt
                                (runGet (owner_GetSelectionOwnerReply `fmap` deserialize))
       let req = MkGetSelectionOwner selection
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
convertSelection ::
                   Graphics.XHB.Connection.Types.Connection ->
                     ConvertSelection -> IO ()
convertSelection c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
sendEvent ::
            Graphics.XHB.Connection.Types.Connection -> SendEvent -> IO ()
sendEvent c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
grabPointer ::
              Graphics.XHB.Connection.Types.Connection ->
                GrabPointer -> IO (Receipt GrabStatus)
grabPointer c req
  = do (receipt, rReceipt) <- newEmptyReceipt
                                (runGet (status_GrabPointerReply `fmap` deserialize))
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
ungrabPointer ::
                Graphics.XHB.Connection.Types.Connection -> TIMESTAMP -> IO ()
ungrabPointer c time
  = do let req = MkUngrabPointer time
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
grabButton ::
             Graphics.XHB.Connection.Types.Connection -> GrabButton -> IO ()
grabButton c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
ungrabButton ::
               Graphics.XHB.Connection.Types.Connection -> UngrabButton -> IO ()
ungrabButton c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
changeActivePointerGrab ::
                          Graphics.XHB.Connection.Types.Connection ->
                            ChangeActivePointerGrab -> IO ()
changeActivePointerGrab c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
grabKeyboard ::
               Graphics.XHB.Connection.Types.Connection ->
                 GrabKeyboard -> IO (Receipt GrabStatus)
grabKeyboard c req
  = do (receipt, rReceipt) <- newEmptyReceipt
                                (runGet (status_GrabKeyboardReply `fmap` deserialize))
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
ungrabKeyboard ::
                 Graphics.XHB.Connection.Types.Connection -> TIMESTAMP -> IO ()
ungrabKeyboard c time
  = do let req = MkUngrabKeyboard time
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
grabKey ::
          Graphics.XHB.Connection.Types.Connection -> GrabKey -> IO ()
grabKey c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
ungrabKey ::
            Graphics.XHB.Connection.Types.Connection -> UngrabKey -> IO ()
ungrabKey c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
allowEvents ::
              Graphics.XHB.Connection.Types.Connection ->
                Allow -> TIMESTAMP -> IO ()
allowEvents c mode time
  = do let req = MkAllowEvents mode time
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
queryPointer ::
               Graphics.XHB.Connection.Types.Connection ->
                 WINDOW -> IO (Receipt QueryPointerReply)
queryPointer c window
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkQueryPointer window
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
getMotionEvents ::
                  Graphics.XHB.Connection.Types.Connection ->
                    GetMotionEvents -> IO (Receipt GetMotionEventsReply)
getMotionEvents c req
  = do (receipt, rReceipt) <- newDeserReceipt
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
translateCoordinates ::
                       Graphics.XHB.Connection.Types.Connection ->
                         TranslateCoordinates -> IO (Receipt TranslateCoordinatesReply)
translateCoordinates c req
  = do (receipt, rReceipt) <- newDeserReceipt
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
warpPointer ::
              Graphics.XHB.Connection.Types.Connection -> WarpPointer -> IO ()
warpPointer c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
setInputFocus ::
                Graphics.XHB.Connection.Types.Connection -> SetInputFocus -> IO ()
setInputFocus c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
getInputFocus ::
                Graphics.XHB.Connection.Types.Connection ->
                  IO (Receipt GetInputFocusReply)
getInputFocus c
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkGetInputFocus
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
queryKeymap ::
              Graphics.XHB.Connection.Types.Connection -> IO (Receipt [Word8])
queryKeymap c
  = do (receipt, rReceipt) <- newEmptyReceipt
                                (runGet (keys_QueryKeymapReply `fmap` deserialize))
       let req = MkQueryKeymap
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
openFont ::
           Graphics.XHB.Connection.Types.Connection -> OpenFont -> IO ()
openFont c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
closeFont ::
            Graphics.XHB.Connection.Types.Connection -> FONT -> IO ()
closeFont c font
  = do let req = MkCloseFont font
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
queryFont ::
            Graphics.XHB.Connection.Types.Connection ->
              FONTABLE -> IO (Receipt QueryFontReply)
queryFont c font
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkQueryFont font
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
queryTextExtents ::
                   Graphics.XHB.Connection.Types.Connection ->
                     FONTABLE -> [CHAR2B] -> IO (Receipt QueryTextExtentsReply)
queryTextExtents c font string
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkQueryTextExtents font string
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
listFonts ::
            Graphics.XHB.Connection.Types.Connection ->
              ListFonts -> IO (Receipt ListFontsReply)
listFonts c req
  = do (receipt, rReceipt) <- newDeserReceipt
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
listFontsWithInfo ::
                    Graphics.XHB.Connection.Types.Connection ->
                      ListFontsWithInfo -> IO (Receipt ListFontsWithInfoReply)
listFontsWithInfo c req
  = do (receipt, rReceipt) <- newDeserReceipt
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
setFontPath ::
              Graphics.XHB.Connection.Types.Connection ->
                Word16 -> [CChar] -> IO ()
setFontPath c font_qty path
  = do let req = MkSetFontPath font_qty path
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
getFontPath ::
              Graphics.XHB.Connection.Types.Connection ->
                IO (Receipt GetFontPathReply)
getFontPath c
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkGetFontPath
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
createPixmap ::
               Graphics.XHB.Connection.Types.Connection -> CreatePixmap -> IO ()
createPixmap c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
freePixmap ::
             Graphics.XHB.Connection.Types.Connection -> PIXMAP -> IO ()
freePixmap c pixmap
  = do let req = MkFreePixmap pixmap
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
createGC ::
           Graphics.XHB.Connection.Types.Connection -> CreateGC -> IO ()
createGC c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
changeGC ::
           Graphics.XHB.Connection.Types.Connection ->
             GCONTEXT -> ValueParam Word32 -> IO ()
changeGC c gc value
  = do let req = MkChangeGC gc value
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
copyGC ::
         Graphics.XHB.Connection.Types.Connection -> CopyGC -> IO ()
copyGC c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
setDashes ::
            Graphics.XHB.Connection.Types.Connection -> SetDashes -> IO ()
setDashes c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
setClipRectangles ::
                    Graphics.XHB.Connection.Types.Connection ->
                      SetClipRectangles -> IO ()
setClipRectangles c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
freeGC ::
         Graphics.XHB.Connection.Types.Connection -> GCONTEXT -> IO ()
freeGC c gc
  = do let req = MkFreeGC gc
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
clearArea ::
            Graphics.XHB.Connection.Types.Connection -> ClearArea -> IO ()
clearArea c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
copyArea ::
           Graphics.XHB.Connection.Types.Connection -> CopyArea -> IO ()
copyArea c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
copyPlane ::
            Graphics.XHB.Connection.Types.Connection -> CopyPlane -> IO ()
copyPlane c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
polyPoint ::
            Graphics.XHB.Connection.Types.Connection -> PolyPoint -> IO ()
polyPoint c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
polyLine ::
           Graphics.XHB.Connection.Types.Connection -> PolyLine -> IO ()
polyLine c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
polySegment ::
              Graphics.XHB.Connection.Types.Connection -> PolySegment -> IO ()
polySegment c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
polyRectangle ::
                Graphics.XHB.Connection.Types.Connection -> PolyRectangle -> IO ()
polyRectangle c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
polyArc ::
          Graphics.XHB.Connection.Types.Connection -> PolyArc -> IO ()
polyArc c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
fillPoly ::
           Graphics.XHB.Connection.Types.Connection -> FillPoly -> IO ()
fillPoly c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
polyFillRectangle ::
                    Graphics.XHB.Connection.Types.Connection ->
                      PolyFillRectangle -> IO ()
polyFillRectangle c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
polyFillArc ::
              Graphics.XHB.Connection.Types.Connection -> PolyFillArc -> IO ()
polyFillArc c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
putImage ::
           Graphics.XHB.Connection.Types.Connection -> PutImage -> IO ()
putImage c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
getImage ::
           Graphics.XHB.Connection.Types.Connection ->
             GetImage -> IO (Receipt GetImageReply)
getImage c req
  = do (receipt, rReceipt) <- newDeserReceipt
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
polyText8 ::
            Graphics.XHB.Connection.Types.Connection -> PolyText8 -> IO ()
polyText8 c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
polyText16 ::
             Graphics.XHB.Connection.Types.Connection -> PolyText16 -> IO ()
polyText16 c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
imageText8 ::
             Graphics.XHB.Connection.Types.Connection -> ImageText8 -> IO ()
imageText8 c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
imageText16 ::
              Graphics.XHB.Connection.Types.Connection -> ImageText16 -> IO ()
imageText16 c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
createColormap ::
                 Graphics.XHB.Connection.Types.Connection -> CreateColormap -> IO ()
createColormap c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
freeColormap ::
               Graphics.XHB.Connection.Types.Connection -> COLORMAP -> IO ()
freeColormap c cmap
  = do let req = MkFreeColormap cmap
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
copyColormapAndFree ::
                      Graphics.XHB.Connection.Types.Connection ->
                        COLORMAP -> COLORMAP -> IO ()
copyColormapAndFree c mid src_cmap
  = do let req = MkCopyColormapAndFree mid src_cmap
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
installColormap ::
                  Graphics.XHB.Connection.Types.Connection -> COLORMAP -> IO ()
installColormap c cmap
  = do let req = MkInstallColormap cmap
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
uninstallColormap ::
                    Graphics.XHB.Connection.Types.Connection -> COLORMAP -> IO ()
uninstallColormap c cmap
  = do let req = MkUninstallColormap cmap
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
listInstalledColormaps ::
                         Graphics.XHB.Connection.Types.Connection ->
                           WINDOW -> IO (Receipt ListInstalledColormapsReply)
listInstalledColormaps c window
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkListInstalledColormaps window
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
allocColor ::
             Graphics.XHB.Connection.Types.Connection ->
               AllocColor -> IO (Receipt AllocColorReply)
allocColor c req
  = do (receipt, rReceipt) <- newDeserReceipt
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
allocNamedColor ::
                  Graphics.XHB.Connection.Types.Connection ->
                    AllocNamedColor -> IO (Receipt AllocNamedColorReply)
allocNamedColor c req
  = do (receipt, rReceipt) <- newDeserReceipt
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
allocColorCells ::
                  Graphics.XHB.Connection.Types.Connection ->
                    AllocColorCells -> IO (Receipt AllocColorCellsReply)
allocColorCells c req
  = do (receipt, rReceipt) <- newDeserReceipt
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
allocColorPlanes ::
                   Graphics.XHB.Connection.Types.Connection ->
                     AllocColorPlanes -> IO (Receipt AllocColorPlanesReply)
allocColorPlanes c req
  = do (receipt, rReceipt) <- newDeserReceipt
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
freeColors ::
             Graphics.XHB.Connection.Types.Connection -> FreeColors -> IO ()
freeColors c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
storeColors ::
              Graphics.XHB.Connection.Types.Connection ->
                COLORMAP -> [COLORITEM] -> IO ()
storeColors c cmap items
  = do let req = MkStoreColors cmap items
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
storeNamedColor ::
                  Graphics.XHB.Connection.Types.Connection ->
                    StoreNamedColor -> IO ()
storeNamedColor c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
queryColors ::
              Graphics.XHB.Connection.Types.Connection ->
                COLORMAP -> [Word32] -> IO (Receipt QueryColorsReply)
queryColors c cmap pixels
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkQueryColors cmap pixels
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
lookupColor ::
              Graphics.XHB.Connection.Types.Connection ->
                LookupColor -> IO (Receipt LookupColorReply)
lookupColor c req
  = do (receipt, rReceipt) <- newDeserReceipt
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
createCursor ::
               Graphics.XHB.Connection.Types.Connection -> CreateCursor -> IO ()
createCursor c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
createGlyphCursor ::
                    Graphics.XHB.Connection.Types.Connection ->
                      CreateGlyphCursor -> IO ()
createGlyphCursor c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
freeCursor ::
             Graphics.XHB.Connection.Types.Connection -> CURSOR -> IO ()
freeCursor c cursor
  = do let req = MkFreeCursor cursor
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
recolorCursor ::
                Graphics.XHB.Connection.Types.Connection -> RecolorCursor -> IO ()
recolorCursor c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
queryBestSize ::
                Graphics.XHB.Connection.Types.Connection ->
                  QueryBestSize -> IO (Receipt QueryBestSizeReply)
queryBestSize c req
  = do (receipt, rReceipt) <- newDeserReceipt
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
queryExtension ::
                 Graphics.XHB.Connection.Types.Connection ->
                   Word16 -> [CChar] -> IO (Receipt QueryExtensionReply)
queryExtension c name_len name
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkQueryExtension name_len name
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
listExtensions ::
                 Graphics.XHB.Connection.Types.Connection ->
                   IO (Receipt ListExtensionsReply)
listExtensions c
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkListExtensions
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
changeKeyboardMapping ::
                        Graphics.XHB.Connection.Types.Connection ->
                          ChangeKeyboardMapping -> IO ()
changeKeyboardMapping c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
getKeyboardMapping ::
                     Graphics.XHB.Connection.Types.Connection ->
                       KEYCODE -> Word8 -> IO (Receipt GetKeyboardMappingReply)
getKeyboardMapping c first_keycode count
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkGetKeyboardMapping first_keycode count
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
changeKeyboardControl ::
                        Graphics.XHB.Connection.Types.Connection ->
                          ValueParam Word32 -> IO ()
changeKeyboardControl c value
  = do let req = MkChangeKeyboardControl value
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
getKeyboardControl ::
                     Graphics.XHB.Connection.Types.Connection ->
                       IO (Receipt GetKeyboardControlReply)
getKeyboardControl c
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkGetKeyboardControl
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
bell :: Graphics.XHB.Connection.Types.Connection -> Int8 -> IO ()
bell c percent
  = do let req = MkBell percent
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
changePointerControl ::
                       Graphics.XHB.Connection.Types.Connection ->
                         ChangePointerControl -> IO ()
changePointerControl c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
getPointerControl ::
                    Graphics.XHB.Connection.Types.Connection ->
                      IO (Receipt GetPointerControlReply)
getPointerControl c
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkGetPointerControl
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
setScreenSaver ::
                 Graphics.XHB.Connection.Types.Connection -> SetScreenSaver -> IO ()
setScreenSaver c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
getScreenSaver ::
                 Graphics.XHB.Connection.Types.Connection ->
                   IO (Receipt GetScreenSaverReply)
getScreenSaver c
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkGetScreenSaver
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
changeHosts ::
              Graphics.XHB.Connection.Types.Connection -> ChangeHosts -> IO ()
changeHosts c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
listHosts ::
            Graphics.XHB.Connection.Types.Connection ->
              IO (Receipt ListHostsReply)
listHosts c
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkListHosts
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
setAccessControl ::
                   Graphics.XHB.Connection.Types.Connection -> AccessControl -> IO ()
setAccessControl c mode
  = do let req = MkSetAccessControl mode
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
setCloseDownMode ::
                   Graphics.XHB.Connection.Types.Connection -> CloseDown -> IO ()
setCloseDownMode c mode
  = do let req = MkSetCloseDownMode mode
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
killClient ::
             Graphics.XHB.Connection.Types.Connection -> Kill -> IO ()
killClient c resource
  = do let req = MkKillClient resource
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
rotateProperties ::
                   Graphics.XHB.Connection.Types.Connection ->
                     RotateProperties -> IO ()
rotateProperties c req
  = do let chunk = runPut (serialize req)
       sendRequest c chunk
 
forceScreenSaver ::
                   Graphics.XHB.Connection.Types.Connection -> ScreenSaver -> IO ()
forceScreenSaver c mode
  = do let req = MkForceScreenSaver mode
       let chunk = runPut (serialize req)
       sendRequest c chunk
 
setPointerMapping ::
                    Graphics.XHB.Connection.Types.Connection ->
                      Word8 -> [Word8] -> IO (Receipt MappingStatus)
setPointerMapping c map_len map
  = do (receipt, rReceipt) <- newEmptyReceipt
                                (runGet (status_SetPointerMappingReply `fmap` deserialize))
       let req = MkSetPointerMapping map_len map
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
getPointerMapping ::
                    Graphics.XHB.Connection.Types.Connection ->
                      IO (Receipt GetPointerMappingReply)
getPointerMapping c
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkGetPointerMapping
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
setModifierMapping ::
                     Graphics.XHB.Connection.Types.Connection ->
                       Word8 -> [KEYCODE] -> IO (Receipt MappingStatus)
setModifierMapping c keycodes_per_modifier keycodes
  = do (receipt, rReceipt) <- newEmptyReceipt
                                (runGet (status_SetModifierMappingReply `fmap` deserialize))
       let req = MkSetModifierMapping keycodes_per_modifier keycodes
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt
 
getModifierMapping ::
                     Graphics.XHB.Connection.Types.Connection ->
                       IO (Receipt GetModifierMappingReply)
getModifierMapping c
  = do (receipt, rReceipt) <- newDeserReceipt
       let req = MkGetModifierMapping
       let chunk = runPut (serialize req)
       sendRequestWithReply c chunk rReceipt
       return receipt