module Graphics.Aosd.AOSD_H where
import Foreign.Ptr (Ptr,FunPtr,plusPtr)
import Foreign.Ptr (wordPtrToPtr,castPtrToFunPtr)
import Foreign.Storable
import Foreign.C.Types
import Foreign.C.String (CString,CStringLen,CWString,CWStringLen)
import Foreign.Marshal.Alloc (alloca)
import Foreign.Marshal.Array (peekArray,pokeArray)
import Data.Int
import Data.Word
import Graphics.Rendering.Cairo.Types
data C'Aosd = C'Aosd
type C'AosdCoordinate = CUInt
c'COORDINATE_MINIMUM = 0
c'COORDINATE_MINIMUM :: (Num a) => a
c'COORDINATE_CENTER = 1
c'COORDINATE_CENTER :: (Num a) => a
c'COORDINATE_MAXIMUM = 2
c'COORDINATE_MAXIMUM :: (Num a) => a
data C'AosdMouseEvent = C'AosdMouseEvent{
c'AosdMouseEvent'x :: CInt,
c'AosdMouseEvent'y :: CInt,
c'AosdMouseEvent'x_root :: CInt,
c'AosdMouseEvent'y_root :: CInt,
c'AosdMouseEvent'button :: CUInt,
c'AosdMouseEvent'time :: CULong
} deriving (Eq,Show)
p'AosdMouseEvent'x p = plusPtr p 0
p'AosdMouseEvent'x :: Ptr (C'AosdMouseEvent) -> Ptr (CInt)
p'AosdMouseEvent'y p = plusPtr p 4
p'AosdMouseEvent'y :: Ptr (C'AosdMouseEvent) -> Ptr (CInt)
p'AosdMouseEvent'x_root p = plusPtr p 8
p'AosdMouseEvent'x_root :: Ptr (C'AosdMouseEvent) -> Ptr (CInt)
p'AosdMouseEvent'y_root p = plusPtr p 12
p'AosdMouseEvent'y_root :: Ptr (C'AosdMouseEvent) -> Ptr (CInt)
p'AosdMouseEvent'button p = plusPtr p 20
p'AosdMouseEvent'button :: Ptr (C'AosdMouseEvent) -> Ptr (CUInt)
p'AosdMouseEvent'time p = plusPtr p 24
p'AosdMouseEvent'time :: Ptr (C'AosdMouseEvent) -> Ptr (CULong)
instance Storable C'AosdMouseEvent where
sizeOf _ = 28
alignment = sizeOf
peek p = do
v0 <- peekByteOff p 0
v1 <- peekByteOff p 4
v2 <- peekByteOff p 8
v3 <- peekByteOff p 12
v4 <- peekByteOff p 20
v5 <- peekByteOff p 24
return $ C'AosdMouseEvent v0 v1 v2 v3 v4 v5
poke p (C'AosdMouseEvent v0 v1 v2 v3 v4 v5) = do
pokeByteOff p 0 v0
pokeByteOff p 4 v1
pokeByteOff p 8 v2
pokeByteOff p 12 v3
pokeByteOff p 20 v4
pokeByteOff p 24 v5
return ()
type C'AosdRenderer = FunPtr (Cairo -> Ptr () -> IO ())
foreign import ccall "wrapper" mk'AosdRenderer
:: (Cairo -> Ptr () -> IO ()) -> IO C'AosdRenderer
foreign import ccall "dynamic" mK'AosdRenderer
:: C'AosdRenderer -> (Cairo -> Ptr () -> IO ())
type C'AosdMouseEventCb = FunPtr (Ptr C'AosdMouseEvent -> Ptr () -> IO ())
foreign import ccall "wrapper" mk'AosdMouseEventCb
:: (Ptr C'AosdMouseEvent -> Ptr () -> IO ()) -> IO C'AosdMouseEventCb
foreign import ccall "dynamic" mK'AosdMouseEventCb
:: C'AosdMouseEventCb -> (Ptr C'AosdMouseEvent -> Ptr () -> IO ())
type C'AosdTransparency = CUInt
c'TRANSPARENCY_NONE = 0
c'TRANSPARENCY_NONE :: (Num a) => a
c'TRANSPARENCY_FAKE = 1
c'TRANSPARENCY_FAKE :: (Num a) => a
c'TRANSPARENCY_COMPOSITE = 2
c'TRANSPARENCY_COMPOSITE :: (Num a) => a
data C'XClassHint = C'XClassHint{
c'XClassHint'res_name :: CString,
c'XClassHint'res_class :: CString
} deriving (Eq,Show)
p'XClassHint'res_name p = plusPtr p 0
p'XClassHint'res_name :: Ptr (C'XClassHint) -> Ptr (CString)
p'XClassHint'res_class p = plusPtr p 4
p'XClassHint'res_class :: Ptr (C'XClassHint) -> Ptr (CString)
instance Storable C'XClassHint where
sizeOf _ = 8
alignment = sizeOf
peek p = do
v0 <- peekByteOff p 0
v1 <- peekByteOff p 4
return $ C'XClassHint v0 v1
poke p (C'XClassHint v0 v1) = do
pokeByteOff p 0 v0
pokeByteOff p 4 v1
return ()
foreign import ccall "aosd_new" c'aosd_new
:: IO (Ptr C'Aosd)
foreign import ccall "&aosd_new" p'aosd_new
:: FunPtr (IO (Ptr C'Aosd))
foreign import ccall "aosd_destroy" c'aosd_destroy
:: Ptr C'Aosd -> IO ()
foreign import ccall "&aosd_destroy" p'aosd_destroy
:: FunPtr (Ptr C'Aosd -> IO ())
foreign import ccall "aosd_set_name" c'aosd_set_name
:: Ptr C'Aosd -> Ptr C'XClassHint -> IO ()
foreign import ccall "&aosd_set_name" p'aosd_set_name
:: FunPtr (Ptr C'Aosd -> Ptr C'XClassHint -> IO ())
foreign import ccall "aosd_set_names" c'aosd_set_names
:: Ptr C'Aosd -> CString -> CString -> IO ()
foreign import ccall "&aosd_set_names" p'aosd_set_names
:: FunPtr (Ptr C'Aosd -> CString -> CString -> IO ())
foreign import ccall "aosd_set_transparency" c'aosd_set_transparency
:: Ptr C'Aosd -> C'AosdTransparency -> IO ()
foreign import ccall "&aosd_set_transparency" p'aosd_set_transparency
:: FunPtr (Ptr C'Aosd -> C'AosdTransparency -> IO ())
foreign import ccall "aosd_set_geometry" c'aosd_set_geometry
:: Ptr C'Aosd -> CInt -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "&aosd_set_geometry" p'aosd_set_geometry
:: FunPtr (Ptr C'Aosd -> CInt -> CInt -> CInt -> CInt -> IO ())
foreign import ccall "aosd_set_position" c'aosd_set_position
:: Ptr C'Aosd -> CUInt -> CInt -> CInt -> IO ()
foreign import ccall "&aosd_set_position" p'aosd_set_position
:: FunPtr (Ptr C'Aosd -> CUInt -> CInt -> CInt -> IO ())
foreign import ccall "aosd_set_position_offset" c'aosd_set_position_offset
:: Ptr C'Aosd -> CInt -> CInt -> IO ()
foreign import ccall "&aosd_set_position_offset" p'aosd_set_position_offset
:: FunPtr (Ptr C'Aosd -> CInt -> CInt -> IO ())
foreign import ccall "aosd_set_position_with_offset" c'aosd_set_position_with_offset
:: Ptr C'Aosd -> C'AosdCoordinate -> C'AosdCoordinate -> CInt -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "&aosd_set_position_with_offset" p'aosd_set_position_with_offset
:: FunPtr (Ptr C'Aosd -> C'AosdCoordinate -> C'AosdCoordinate -> CInt -> CInt -> CInt -> CInt -> IO ())
foreign import ccall "aosd_set_renderer" c'aosd_set_renderer
:: Ptr C'Aosd -> C'AosdRenderer -> Ptr () -> IO ()
foreign import ccall "&aosd_set_renderer" p'aosd_set_renderer
:: FunPtr (Ptr C'Aosd -> C'AosdRenderer -> Ptr () -> IO ())
foreign import ccall "aosd_set_mouse_event_cb" c'aosd_set_mouse_event_cb
:: Ptr C'Aosd -> C'AosdMouseEventCb -> Ptr () -> IO ()
foreign import ccall "&aosd_set_mouse_event_cb" p'aosd_set_mouse_event_cb
:: FunPtr (Ptr C'Aosd -> C'AosdMouseEventCb -> Ptr () -> IO ())
foreign import ccall "aosd_set_hide_upon_mouse_event" c'aosd_set_hide_upon_mouse_event
:: Ptr C'Aosd -> CInt -> IO ()
foreign import ccall "&aosd_set_hide_upon_mouse_event" p'aosd_set_hide_upon_mouse_event
:: FunPtr (Ptr C'Aosd -> CInt -> IO ())
foreign import ccall "aosd_render" c'aosd_render
:: Ptr C'Aosd -> IO ()
foreign import ccall "&aosd_render" p'aosd_render
:: FunPtr (Ptr C'Aosd -> IO ())
foreign import ccall "aosd_show" c'aosd_show
:: Ptr C'Aosd -> IO ()
foreign import ccall "&aosd_show" p'aosd_show
:: FunPtr (Ptr C'Aosd -> IO ())
foreign import ccall "aosd_hide" c'aosd_hide
:: Ptr C'Aosd -> IO ()
foreign import ccall "&aosd_hide" p'aosd_hide
:: FunPtr (Ptr C'Aosd -> IO ())
foreign import ccall "aosd_loop_once" c'aosd_loop_once
:: Ptr C'Aosd -> IO ()
foreign import ccall "&aosd_loop_once" p'aosd_loop_once
:: FunPtr (Ptr C'Aosd -> IO ())
foreign import ccall "aosd_loop_for" c'aosd_loop_for
:: Ptr C'Aosd -> CUInt -> IO ()
foreign import ccall "&aosd_loop_for" p'aosd_loop_for
:: FunPtr (Ptr C'Aosd -> CUInt -> IO ())
foreign import ccall "aosd_flash" c'aosd_flash
:: Ptr C'Aosd -> CUInt -> CUInt -> CUInt -> IO ()
foreign import ccall "&aosd_flash" p'aosd_flash
:: FunPtr (Ptr C'Aosd -> CUInt -> CUInt -> CUInt -> IO ())