module Graphics.UI.Gtk.Gdk.Screen (
Screen,
ScreenClass,
castToScreen, gTypeScreen,
toScreen,
screenGetDefault,
screenGetSystemColormap,
screenGetRGBAColormap,
screenGetDefaultColormap,
screenSetDefaultColormap,
screenGetSystemVisual,
screenIsComposited,
screenGetRootWindow,
screenGetDisplay,
screenGetNumber,
screenGetWidth,
screenGetHeight,
screenGetWidthMm,
screenGetHeightMm,
screenGetWidthMM,
screenGetHeightMM,
screenListVisuals,
screenGetToplevelWindows,
screenMakeDisplayName,
screenGetNMonitors,
screenGetMonitorGeometry,
screenGetMonitorAtPoint,
screenGetMonitorAtWindow,
screenGetMonitorHeightMm,
screenGetMonitorWidthMm,
screenGetMonitorPlugName,
screenGetActiveWindow,
screenGetWindowStack,
screenFontOptions,
screenResolution,
screenDefaultColormap,
screenSizeChanged,
screenCompositedChanged,
screenMonitorsChanged,
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.Signals
import System.Glib.Attributes
import System.Glib.Properties
import System.Glib.GList
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.Signals
import Graphics.Rendering.Cairo.Types ( FontOptions(..), mkFontOptions,
withFontOptions)
import Graphics.UI.Gtk.General.Structs ( Rectangle(..) )
screenGetDefault ::
IO (Maybe Screen)
screenGetDefault =
maybeNull (makeNewGObject mkScreen) $
gdk_screen_get_default
screenGetDefaultColormap :: Screen
-> IO Colormap
screenGetDefaultColormap self =
makeNewGObject mkColormap $
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_default_colormap argPtr1)
self
screenSetDefaultColormap :: Screen
-> Colormap
-> IO ()
screenSetDefaultColormap self colormap =
(\(Screen arg1) (Colormap arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_screen_set_default_colormap argPtr1 argPtr2)
self
colormap
screenGetSystemColormap :: Screen
-> IO Colormap
screenGetSystemColormap self =
makeNewGObject mkColormap $
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_system_colormap argPtr1)
self
screenGetRGBAColormap :: Screen
-> IO (Maybe Colormap)
screenGetRGBAColormap self =
maybeNull (makeNewGObject mkColormap) $
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_rgba_colormap argPtr1)
self
screenGetSystemVisual :: Screen
-> IO Visual
screenGetSystemVisual self =
makeNewGObject mkVisual $
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_system_visual argPtr1)
self
screenIsComposited :: Screen
-> IO Bool
screenIsComposited self =
liftM toBool $
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_is_composited argPtr1)
self
screenGetRootWindow :: Screen
-> IO DrawWindow
screenGetRootWindow self =
makeNewGObject mkDrawWindow $
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_root_window argPtr1)
self
screenGetDisplay :: Screen
-> IO Display
screenGetDisplay self =
makeNewGObject mkDisplay $
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_display argPtr1)
self
screenGetNumber :: Screen
-> IO Int
screenGetNumber self =
liftM fromIntegral $
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_number argPtr1)
self
screenGetWidth :: Screen
-> IO Int
screenGetWidth self =
liftM fromIntegral $
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_width argPtr1)
self
screenGetHeight :: Screen
-> IO Int
screenGetHeight self =
liftM fromIntegral $
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_height argPtr1)
self
screenGetWidthMM :: Screen
-> IO Int
screenGetWidthMM self =
liftM fromIntegral $
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_width_mm argPtr1)
self
screenGetWidthMm = screenGetWidthMM
screenGetHeightMM :: Screen
-> IO Int
screenGetHeightMM self =
liftM fromIntegral $
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_height_mm argPtr1)
self
screenGetHeightMm = screenGetHeightMM
screenListVisuals :: Screen
-> IO [Visual]
screenListVisuals self =
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_list_visuals argPtr1)
self
>>= fromGList
>>= mapM (makeNewGObject mkVisual . return)
screenGetToplevelWindows :: Screen
-> IO [DrawWindow]
screenGetToplevelWindows self =
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_toplevel_windows argPtr1)
self
>>= fromGList
>>= mapM (makeNewGObject mkDrawWindow . return)
screenMakeDisplayName :: GlibString string => Screen
-> IO string
screenMakeDisplayName self =
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_make_display_name argPtr1)
self
>>= readUTFString
screenGetNMonitors :: Screen
-> IO Int
screenGetNMonitors self =
liftM fromIntegral $
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_n_monitors argPtr1)
self
screenGetMonitorGeometry :: Screen
-> Int
-> IO Rectangle
screenGetMonitorGeometry self monitorNum =
alloca $ \rPtr -> do
(\(Screen arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_monitor_geometry argPtr1 arg2 arg3)
self
(fromIntegral monitorNum)
(castPtr rPtr)
peek rPtr
screenGetMonitorAtPoint :: Screen
-> Int
-> Int
-> IO Int
screenGetMonitorAtPoint self x y =
liftM fromIntegral $
(\(Screen arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_monitor_at_point argPtr1 arg2 arg3)
self
(fromIntegral x)
(fromIntegral y)
screenGetMonitorAtWindow :: Screen
-> DrawWindow
-> IO Int
screenGetMonitorAtWindow self window =
liftM fromIntegral $
(\(Screen arg1) (DrawWindow arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_screen_get_monitor_at_window argPtr1 argPtr2)
self
window
screenGetMonitorHeightMm :: Screen
-> Int
-> IO Int
screenGetMonitorHeightMm self monitorNum =
liftM fromIntegral $
(\(Screen arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_monitor_height_mm argPtr1 arg2)
self
(fromIntegral monitorNum)
screenGetMonitorWidthMm :: Screen
-> Int
-> IO Int
screenGetMonitorWidthMm self monitorNum =
liftM fromIntegral $
(\(Screen arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_monitor_width_mm argPtr1 arg2)
self
(fromIntegral monitorNum)
screenGetMonitorPlugName :: GlibString string => Screen
-> Int
-> IO (Maybe string)
screenGetMonitorPlugName self monitorNum = do
sPtr <-
(\(Screen arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_monitor_plug_name argPtr1 arg2)
self
(fromIntegral monitorNum)
if sPtr==nullPtr then return Nothing else liftM Just $ readUTFString sPtr
screenGetFontOptions :: Screen
-> IO (Maybe FontOptions)
screenGetFontOptions self = do
fPtr <- (\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_font_options argPtr1) self
if fPtr==nullPtr then return Nothing else liftM Just $ mkFontOptions (castPtr fPtr)
screenSetFontOptions :: Screen
-> Maybe FontOptions
-> IO ()
screenSetFontOptions self Nothing =
(\(Screen arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_set_font_options argPtr1 arg2) self nullPtr
screenSetFontOptions self (Just options) =
withFontOptions options $ \fPtr ->
(\(Screen arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_set_font_options argPtr1 arg2) self (castPtr fPtr)
screenGetActiveWindow :: Screen
-> IO (Maybe DrawWindow)
screenGetActiveWindow self =
maybeNull (wrapNewGObject mkDrawWindow) $
(\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_active_window argPtr1)
self
screenGetWindowStack :: Screen
-> IO (Maybe [DrawWindow])
screenGetWindowStack self = do
lPtr <- (\(Screen arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_screen_get_window_stack argPtr1) self
if lPtr==nullPtr then return Nothing else liftM Just $ do
fromGList lPtr >>= mapM (wrapNewGObject mkDrawWindow . return)
screenFontOptions :: Attr Screen (Maybe FontOptions)
screenFontOptions = newAttr
screenGetFontOptions
screenSetFontOptions
screenResolution :: Attr Screen Double
screenResolution = newAttrFromDoubleProperty "resolution"
screenDefaultColormap :: Attr Screen Colormap
screenDefaultColormap = newAttr
screenGetDefaultColormap
screenSetDefaultColormap
screenSizeChanged :: ScreenClass self => Signal self (IO ())
screenSizeChanged = Signal (connect_NONE__NONE "size-changed")
screenCompositedChanged :: ScreenClass self => Signal self (IO ())
screenCompositedChanged = Signal (connect_NONE__NONE "composited-changed")
screenMonitorsChanged :: ScreenClass self => Signal self (IO ())
screenMonitorsChanged = Signal (connect_NONE__NONE "monitors-changed")
foreign import ccall safe "gdk_screen_get_default"
gdk_screen_get_default :: (IO (Ptr Screen))
foreign import ccall safe "gdk_screen_get_default_colormap"
gdk_screen_get_default_colormap :: ((Ptr Screen) -> (IO (Ptr Colormap)))
foreign import ccall safe "gdk_screen_set_default_colormap"
gdk_screen_set_default_colormap :: ((Ptr Screen) -> ((Ptr Colormap) -> (IO ())))
foreign import ccall safe "gdk_screen_get_system_colormap"
gdk_screen_get_system_colormap :: ((Ptr Screen) -> (IO (Ptr Colormap)))
foreign import ccall safe "gdk_screen_get_rgba_colormap"
gdk_screen_get_rgba_colormap :: ((Ptr Screen) -> (IO (Ptr Colormap)))
foreign import ccall safe "gdk_screen_get_system_visual"
gdk_screen_get_system_visual :: ((Ptr Screen) -> (IO (Ptr Visual)))
foreign import ccall safe "gdk_screen_is_composited"
gdk_screen_is_composited :: ((Ptr Screen) -> (IO CInt))
foreign import ccall safe "gdk_screen_get_root_window"
gdk_screen_get_root_window :: ((Ptr Screen) -> (IO (Ptr DrawWindow)))
foreign import ccall safe "gdk_screen_get_display"
gdk_screen_get_display :: ((Ptr Screen) -> (IO (Ptr Display)))
foreign import ccall safe "gdk_screen_get_number"
gdk_screen_get_number :: ((Ptr Screen) -> (IO CInt))
foreign import ccall safe "gdk_screen_get_width"
gdk_screen_get_width :: ((Ptr Screen) -> (IO CInt))
foreign import ccall safe "gdk_screen_get_height"
gdk_screen_get_height :: ((Ptr Screen) -> (IO CInt))
foreign import ccall safe "gdk_screen_get_width_mm"
gdk_screen_get_width_mm :: ((Ptr Screen) -> (IO CInt))
foreign import ccall safe "gdk_screen_get_height_mm"
gdk_screen_get_height_mm :: ((Ptr Screen) -> (IO CInt))
foreign import ccall safe "gdk_screen_list_visuals"
gdk_screen_list_visuals :: ((Ptr Screen) -> (IO (Ptr ())))
foreign import ccall safe "gdk_screen_get_toplevel_windows"
gdk_screen_get_toplevel_windows :: ((Ptr Screen) -> (IO (Ptr ())))
foreign import ccall safe "gdk_screen_make_display_name"
gdk_screen_make_display_name :: ((Ptr Screen) -> (IO (Ptr CChar)))
foreign import ccall safe "gdk_screen_get_n_monitors"
gdk_screen_get_n_monitors :: ((Ptr Screen) -> (IO CInt))
foreign import ccall safe "gdk_screen_get_monitor_geometry"
gdk_screen_get_monitor_geometry :: ((Ptr Screen) -> (CInt -> ((Ptr ()) -> (IO ()))))
foreign import ccall safe "gdk_screen_get_monitor_at_point"
gdk_screen_get_monitor_at_point :: ((Ptr Screen) -> (CInt -> (CInt -> (IO CInt))))
foreign import ccall safe "gdk_screen_get_monitor_at_window"
gdk_screen_get_monitor_at_window :: ((Ptr Screen) -> ((Ptr DrawWindow) -> (IO CInt)))
foreign import ccall safe "gdk_screen_get_monitor_height_mm"
gdk_screen_get_monitor_height_mm :: ((Ptr Screen) -> (CInt -> (IO CInt)))
foreign import ccall safe "gdk_screen_get_monitor_width_mm"
gdk_screen_get_monitor_width_mm :: ((Ptr Screen) -> (CInt -> (IO CInt)))
foreign import ccall safe "gdk_screen_get_monitor_plug_name"
gdk_screen_get_monitor_plug_name :: ((Ptr Screen) -> (CInt -> (IO (Ptr CChar))))
foreign import ccall safe "gdk_screen_get_font_options"
gdk_screen_get_font_options :: ((Ptr Screen) -> (IO (Ptr ())))
foreign import ccall safe "gdk_screen_set_font_options"
gdk_screen_set_font_options :: ((Ptr Screen) -> ((Ptr ()) -> (IO ())))
foreign import ccall safe "gdk_screen_get_active_window"
gdk_screen_get_active_window :: ((Ptr Screen) -> (IO (Ptr DrawWindow)))
foreign import ccall safe "gdk_screen_get_window_stack"
gdk_screen_get_window_stack :: ((Ptr Screen) -> (IO (Ptr ())))