{-# LINE 1 "libraries\\Win32\\Graphics\\Win32\\Window\\AnimateWindow.hsc" #-}
{-# LANGUAGE CPP #-}
module Graphics.Win32.Window.AnimateWindow where
import Graphics.Win32.GDI.Types ( HWND )
import System.Win32.Types ( DWORD, BOOL, failIfFalse_ )
#include "windows_cconv.h"
type AnimateWindowType = DWORD
aW_SLIDE :: AnimateWindowType
aW_SLIDE = 262144
aW_ACTIVATE :: AnimateWindowType
aW_ACTIVATE = 131072
aW_BLEND :: AnimateWindowType
aW_BLEND = 524288
aW_HIDE :: AnimateWindowType
aW_HIDE = 65536
aW_CENTER :: AnimateWindowType
aW_CENTER = 16
aW_HOR_POSITIVE :: AnimateWindowType
aW_HOR_POSITIVE = 1
aW_HOR_POSITIVE :: AnimateWindowType
aW_HOR_NEGATIVE :: AnimateWindowType
aW_HOR_NEGATIVE = 2
aW_HOR_NEGATIVE :: AnimateWindowType
aW_VER_POSITIVE :: AnimateWindowType
aW_VER_POSITIVE = 4
aW_VER_POSITIVE :: AnimateWindowType
aW_VER_NEGATIVE :: AnimateWindowType
aW_VER_NEGATIVE = 8
{-# LINE 34 "libraries\\Win32\\Graphics\\Win32\\Window\\AnimateWindow.hsc" #-}
animateWindow :: HWND -> DWORD -> AnimateWindowType -> IO ()
animateWindow hwnd dwTime dwFlags
= failIfFalse_ "AnimateWindow" $ c_AnimateWindow hwnd dwTime dwFlags
foreign import WINDOWS_CCONV "windows.h AnimateWindow"
c_AnimateWindow :: HWND -> DWORD -> AnimateWindowType -> IO BOOL