{-# LINE 1 "Graphics/X11/Xlib/Types.hsc" #-}
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Graphics.X11.Xlib.Types
-- Copyright   :  (c) Alastair Reid, 1999-2003
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  provisional
-- Portability :  portable
--
-- A collection of type declarations for interfacing with Xlib.
--
-----------------------------------------------------------------------------

-- #hide
module Graphics.X11.Xlib.Types(
        Display(..), Screen(..), Visual(..), GC(..), GCValues, SetWindowAttributes,
        VisualInfo(..),
        Image(..), Point(..), Rectangle(..), Arc(..), Segment(..), Color(..),
        Pixel, Position, Dimension, Angle, ScreenNumber, Buffer
        ) where

import Graphics.X11.Types

-- import Control.Monad( zipWithM_ )
import Data.Int
import Data.Word
import Foreign.C.Types
-- import Foreign.Marshal.Alloc( allocaBytes )
import Foreign.Ptr
import Foreign.Storable( Storable(..) )


{-# LINE 35 "Graphics/X11/Xlib/Types.hsc" #-}
import Data.Data

{-# LINE 37 "Graphics/X11/Xlib/Types.hsc" #-}

import Data.Default.Class



----------------------------------------------------------------
-- Types
----------------------------------------------------------------

-- | pointer to an X11 @Display@ structure
newtype Display    = Display    (Ptr Display)

{-# LINE 49 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Display -> Display -> Bool
(Display -> Display -> Bool)
-> (Display -> Display -> Bool) -> Eq Display
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Display -> Display -> Bool
$c/= :: Display -> Display -> Bool
== :: Display -> Display -> Bool
$c== :: Display -> Display -> Bool
Eq, Eq Display
Eq Display
-> (Display -> Display -> Ordering)
-> (Display -> Display -> Bool)
-> (Display -> Display -> Bool)
-> (Display -> Display -> Bool)
-> (Display -> Display -> Bool)
-> (Display -> Display -> Display)
-> (Display -> Display -> Display)
-> Ord Display
Display -> Display -> Bool
Display -> Display -> Ordering
Display -> Display -> Display
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Display -> Display -> Display
$cmin :: Display -> Display -> Display
max :: Display -> Display -> Display
$cmax :: Display -> Display -> Display
>= :: Display -> Display -> Bool
$c>= :: Display -> Display -> Bool
> :: Display -> Display -> Bool
$c> :: Display -> Display -> Bool
<= :: Display -> Display -> Bool
$c<= :: Display -> Display -> Bool
< :: Display -> Display -> Bool
$c< :: Display -> Display -> Bool
compare :: Display -> Display -> Ordering
$ccompare :: Display -> Display -> Ordering
Ord, Int -> Display -> ShowS
[Display] -> ShowS
Display -> String
(Int -> Display -> ShowS)
-> (Display -> String) -> ([Display] -> ShowS) -> Show Display
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Display] -> ShowS
$cshowList :: [Display] -> ShowS
show :: Display -> String
$cshow :: Display -> String
showsPrec :: Int -> Display -> ShowS
$cshowsPrec :: Int -> Display -> ShowS
Show, Typeable, Typeable Display
Typeable Display
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Display -> c Display)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Display)
-> (Display -> Constr)
-> (Display -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Display))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Display))
-> ((forall b. Data b => b -> b) -> Display -> Display)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Display -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Display -> r)
-> (forall u. (forall d. Data d => d -> u) -> Display -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Display -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Display -> m Display)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Display -> m Display)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Display -> m Display)
-> Data Display
Display -> DataType
Display -> Constr
(forall b. Data b => b -> b) -> Display -> Display
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Display -> u
forall u. (forall d. Data d => d -> u) -> Display -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Display -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Display -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Display -> m Display
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Display -> m Display
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Display
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Display -> c Display
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Display)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Display)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Display -> m Display
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Display -> m Display
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Display -> m Display
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Display -> m Display
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Display -> m Display
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Display -> m Display
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Display -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Display -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Display -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Display -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Display -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Display -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Display -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Display -> r
gmapT :: (forall b. Data b => b -> b) -> Display -> Display
$cgmapT :: (forall b. Data b => b -> b) -> Display -> Display
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Display)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Display)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Display)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Display)
dataTypeOf :: Display -> DataType
$cdataTypeOf :: Display -> DataType
toConstr :: Display -> Constr
$ctoConstr :: Display -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Display
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Display
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Display -> c Display
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Display -> c Display
Data)

{-# LINE 53 "Graphics/X11/Xlib/Types.hsc" #-}

-- | pointer to an X11 @Screen@ structure
newtype Screen     = Screen     (Ptr Screen)

{-# LINE 57 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Screen -> Screen -> Bool
(Screen -> Screen -> Bool)
-> (Screen -> Screen -> Bool) -> Eq Screen
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Screen -> Screen -> Bool
$c/= :: Screen -> Screen -> Bool
== :: Screen -> Screen -> Bool
$c== :: Screen -> Screen -> Bool
Eq, Eq Screen
Eq Screen
-> (Screen -> Screen -> Ordering)
-> (Screen -> Screen -> Bool)
-> (Screen -> Screen -> Bool)
-> (Screen -> Screen -> Bool)
-> (Screen -> Screen -> Bool)
-> (Screen -> Screen -> Screen)
-> (Screen -> Screen -> Screen)
-> Ord Screen
Screen -> Screen -> Bool
Screen -> Screen -> Ordering
Screen -> Screen -> Screen
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Screen -> Screen -> Screen
$cmin :: Screen -> Screen -> Screen
max :: Screen -> Screen -> Screen
$cmax :: Screen -> Screen -> Screen
>= :: Screen -> Screen -> Bool
$c>= :: Screen -> Screen -> Bool
> :: Screen -> Screen -> Bool
$c> :: Screen -> Screen -> Bool
<= :: Screen -> Screen -> Bool
$c<= :: Screen -> Screen -> Bool
< :: Screen -> Screen -> Bool
$c< :: Screen -> Screen -> Bool
compare :: Screen -> Screen -> Ordering
$ccompare :: Screen -> Screen -> Ordering
Ord, Int -> Screen -> ShowS
[Screen] -> ShowS
Screen -> String
(Int -> Screen -> ShowS)
-> (Screen -> String) -> ([Screen] -> ShowS) -> Show Screen
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Screen] -> ShowS
$cshowList :: [Screen] -> ShowS
show :: Screen -> String
$cshow :: Screen -> String
showsPrec :: Int -> Screen -> ShowS
$cshowsPrec :: Int -> Screen -> ShowS
Show, Typeable, Typeable Screen
Typeable Screen
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Screen -> c Screen)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Screen)
-> (Screen -> Constr)
-> (Screen -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Screen))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Screen))
-> ((forall b. Data b => b -> b) -> Screen -> Screen)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Screen -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Screen -> r)
-> (forall u. (forall d. Data d => d -> u) -> Screen -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Screen -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Screen -> m Screen)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Screen -> m Screen)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Screen -> m Screen)
-> Data Screen
Screen -> DataType
Screen -> Constr
(forall b. Data b => b -> b) -> Screen -> Screen
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Screen -> u
forall u. (forall d. Data d => d -> u) -> Screen -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Screen -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Screen -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Screen -> m Screen
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Screen -> m Screen
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Screen
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Screen -> c Screen
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Screen)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Screen)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Screen -> m Screen
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Screen -> m Screen
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Screen -> m Screen
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Screen -> m Screen
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Screen -> m Screen
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Screen -> m Screen
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Screen -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Screen -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Screen -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Screen -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Screen -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Screen -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Screen -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Screen -> r
gmapT :: (forall b. Data b => b -> b) -> Screen -> Screen
$cgmapT :: (forall b. Data b => b -> b) -> Screen -> Screen
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Screen)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Screen)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Screen)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Screen)
dataTypeOf :: Screen -> DataType
$cdataTypeOf :: Screen -> DataType
toConstr :: Screen -> Constr
$ctoConstr :: Screen -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Screen
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Screen
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Screen -> c Screen
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Screen -> c Screen
Data)

{-# LINE 61 "Graphics/X11/Xlib/Types.hsc" #-}

-- | pointer to an X11 @Visual@ structure
newtype Visual     = Visual     (Ptr Visual)

{-# LINE 65 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Visual -> Visual -> Bool
(Visual -> Visual -> Bool)
-> (Visual -> Visual -> Bool) -> Eq Visual
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Visual -> Visual -> Bool
$c/= :: Visual -> Visual -> Bool
== :: Visual -> Visual -> Bool
$c== :: Visual -> Visual -> Bool
Eq, Eq Visual
Eq Visual
-> (Visual -> Visual -> Ordering)
-> (Visual -> Visual -> Bool)
-> (Visual -> Visual -> Bool)
-> (Visual -> Visual -> Bool)
-> (Visual -> Visual -> Bool)
-> (Visual -> Visual -> Visual)
-> (Visual -> Visual -> Visual)
-> Ord Visual
Visual -> Visual -> Bool
Visual -> Visual -> Ordering
Visual -> Visual -> Visual
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Visual -> Visual -> Visual
$cmin :: Visual -> Visual -> Visual
max :: Visual -> Visual -> Visual
$cmax :: Visual -> Visual -> Visual
>= :: Visual -> Visual -> Bool
$c>= :: Visual -> Visual -> Bool
> :: Visual -> Visual -> Bool
$c> :: Visual -> Visual -> Bool
<= :: Visual -> Visual -> Bool
$c<= :: Visual -> Visual -> Bool
< :: Visual -> Visual -> Bool
$c< :: Visual -> Visual -> Bool
compare :: Visual -> Visual -> Ordering
$ccompare :: Visual -> Visual -> Ordering
Ord, Int -> Visual -> ShowS
[Visual] -> ShowS
Visual -> String
(Int -> Visual -> ShowS)
-> (Visual -> String) -> ([Visual] -> ShowS) -> Show Visual
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Visual] -> ShowS
$cshowList :: [Visual] -> ShowS
show :: Visual -> String
$cshow :: Visual -> String
showsPrec :: Int -> Visual -> ShowS
$cshowsPrec :: Int -> Visual -> ShowS
Show, Typeable, Typeable Visual
Typeable Visual
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Visual -> c Visual)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Visual)
-> (Visual -> Constr)
-> (Visual -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Visual))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Visual))
-> ((forall b. Data b => b -> b) -> Visual -> Visual)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Visual -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Visual -> r)
-> (forall u. (forall d. Data d => d -> u) -> Visual -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Visual -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Visual -> m Visual)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Visual -> m Visual)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Visual -> m Visual)
-> Data Visual
Visual -> DataType
Visual -> Constr
(forall b. Data b => b -> b) -> Visual -> Visual
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Visual -> u
forall u. (forall d. Data d => d -> u) -> Visual -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Visual -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Visual -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Visual -> m Visual
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Visual -> m Visual
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Visual
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Visual -> c Visual
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Visual)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Visual)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Visual -> m Visual
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Visual -> m Visual
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Visual -> m Visual
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Visual -> m Visual
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Visual -> m Visual
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Visual -> m Visual
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Visual -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Visual -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Visual -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Visual -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Visual -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Visual -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Visual -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Visual -> r
gmapT :: (forall b. Data b => b -> b) -> Visual -> Visual
$cgmapT :: (forall b. Data b => b -> b) -> Visual -> Visual
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Visual)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Visual)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Visual)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Visual)
dataTypeOf :: Visual -> DataType
$cdataTypeOf :: Visual -> DataType
toConstr :: Visual -> Constr
$ctoConstr :: Visual -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Visual
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Visual
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Visual -> c Visual
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Visual -> c Visual
Data)

{-# LINE 69 "Graphics/X11/Xlib/Types.hsc" #-}

-- | pointer to an X11 @GC@ structure
newtype GC         = GC         (Ptr GC)

{-# LINE 73 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (GC -> GC -> Bool
(GC -> GC -> Bool) -> (GC -> GC -> Bool) -> Eq GC
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GC -> GC -> Bool
$c/= :: GC -> GC -> Bool
== :: GC -> GC -> Bool
$c== :: GC -> GC -> Bool
Eq, Eq GC
Eq GC
-> (GC -> GC -> Ordering)
-> (GC -> GC -> Bool)
-> (GC -> GC -> Bool)
-> (GC -> GC -> Bool)
-> (GC -> GC -> Bool)
-> (GC -> GC -> GC)
-> (GC -> GC -> GC)
-> Ord GC
GC -> GC -> Bool
GC -> GC -> Ordering
GC -> GC -> GC
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GC -> GC -> GC
$cmin :: GC -> GC -> GC
max :: GC -> GC -> GC
$cmax :: GC -> GC -> GC
>= :: GC -> GC -> Bool
$c>= :: GC -> GC -> Bool
> :: GC -> GC -> Bool
$c> :: GC -> GC -> Bool
<= :: GC -> GC -> Bool
$c<= :: GC -> GC -> Bool
< :: GC -> GC -> Bool
$c< :: GC -> GC -> Bool
compare :: GC -> GC -> Ordering
$ccompare :: GC -> GC -> Ordering
Ord, Int -> GC -> ShowS
[GC] -> ShowS
GC -> String
(Int -> GC -> ShowS)
-> (GC -> String) -> ([GC] -> ShowS) -> Show GC
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GC] -> ShowS
$cshowList :: [GC] -> ShowS
show :: GC -> String
$cshow :: GC -> String
showsPrec :: Int -> GC -> ShowS
$cshowsPrec :: Int -> GC -> ShowS
Show, Typeable, Typeable GC
Typeable GC
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> GC -> c GC)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c GC)
-> (GC -> Constr)
-> (GC -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c GC))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GC))
-> ((forall b. Data b => b -> b) -> GC -> GC)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GC -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GC -> r)
-> (forall u. (forall d. Data d => d -> u) -> GC -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> GC -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> GC -> m GC)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> GC -> m GC)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> GC -> m GC)
-> Data GC
GC -> DataType
GC -> Constr
(forall b. Data b => b -> b) -> GC -> GC
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> GC -> u
forall u. (forall d. Data d => d -> u) -> GC -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GC -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GC -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> GC -> m GC
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GC -> m GC
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GC
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GC -> c GC
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c GC)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GC)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GC -> m GC
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GC -> m GC
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GC -> m GC
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GC -> m GC
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> GC -> m GC
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> GC -> m GC
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> GC -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> GC -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> GC -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> GC -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GC -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GC -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GC -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GC -> r
gmapT :: (forall b. Data b => b -> b) -> GC -> GC
$cgmapT :: (forall b. Data b => b -> b) -> GC -> GC
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GC)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GC)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c GC)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c GC)
dataTypeOf :: GC -> DataType
$cdataTypeOf :: GC -> DataType
toConstr :: GC -> Constr
$ctoConstr :: GC -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GC
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GC
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GC -> c GC
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GC -> c GC
Data)

{-# LINE 77 "Graphics/X11/Xlib/Types.hsc" #-}

-- | pointer to an X11 @XGCValues@ structure
newtype GCValues   = GCValues  (Ptr GCValues)

{-# LINE 81 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (GCValues -> GCValues -> Bool
(GCValues -> GCValues -> Bool)
-> (GCValues -> GCValues -> Bool) -> Eq GCValues
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GCValues -> GCValues -> Bool
$c/= :: GCValues -> GCValues -> Bool
== :: GCValues -> GCValues -> Bool
$c== :: GCValues -> GCValues -> Bool
Eq, Eq GCValues
Eq GCValues
-> (GCValues -> GCValues -> Ordering)
-> (GCValues -> GCValues -> Bool)
-> (GCValues -> GCValues -> Bool)
-> (GCValues -> GCValues -> Bool)
-> (GCValues -> GCValues -> Bool)
-> (GCValues -> GCValues -> GCValues)
-> (GCValues -> GCValues -> GCValues)
-> Ord GCValues
GCValues -> GCValues -> Bool
GCValues -> GCValues -> Ordering
GCValues -> GCValues -> GCValues
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GCValues -> GCValues -> GCValues
$cmin :: GCValues -> GCValues -> GCValues
max :: GCValues -> GCValues -> GCValues
$cmax :: GCValues -> GCValues -> GCValues
>= :: GCValues -> GCValues -> Bool
$c>= :: GCValues -> GCValues -> Bool
> :: GCValues -> GCValues -> Bool
$c> :: GCValues -> GCValues -> Bool
<= :: GCValues -> GCValues -> Bool
$c<= :: GCValues -> GCValues -> Bool
< :: GCValues -> GCValues -> Bool
$c< :: GCValues -> GCValues -> Bool
compare :: GCValues -> GCValues -> Ordering
$ccompare :: GCValues -> GCValues -> Ordering
Ord, Int -> GCValues -> ShowS
[GCValues] -> ShowS
GCValues -> String
(Int -> GCValues -> ShowS)
-> (GCValues -> String) -> ([GCValues] -> ShowS) -> Show GCValues
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GCValues] -> ShowS
$cshowList :: [GCValues] -> ShowS
show :: GCValues -> String
$cshow :: GCValues -> String
showsPrec :: Int -> GCValues -> ShowS
$cshowsPrec :: Int -> GCValues -> ShowS
Show, Typeable, Typeable GCValues
Typeable GCValues
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> GCValues -> c GCValues)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c GCValues)
-> (GCValues -> Constr)
-> (GCValues -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c GCValues))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GCValues))
-> ((forall b. Data b => b -> b) -> GCValues -> GCValues)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> GCValues -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> GCValues -> r)
-> (forall u. (forall d. Data d => d -> u) -> GCValues -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> GCValues -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> GCValues -> m GCValues)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> GCValues -> m GCValues)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> GCValues -> m GCValues)
-> Data GCValues
GCValues -> DataType
GCValues -> Constr
(forall b. Data b => b -> b) -> GCValues -> GCValues
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> GCValues -> u
forall u. (forall d. Data d => d -> u) -> GCValues -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GCValues -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GCValues -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> GCValues -> m GCValues
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GCValues -> m GCValues
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GCValues
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GCValues -> c GCValues
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c GCValues)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GCValues)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GCValues -> m GCValues
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GCValues -> m GCValues
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GCValues -> m GCValues
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GCValues -> m GCValues
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> GCValues -> m GCValues
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> GCValues -> m GCValues
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> GCValues -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> GCValues -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> GCValues -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> GCValues -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GCValues -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GCValues -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GCValues -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GCValues -> r
gmapT :: (forall b. Data b => b -> b) -> GCValues -> GCValues
$cgmapT :: (forall b. Data b => b -> b) -> GCValues -> GCValues
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GCValues)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GCValues)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c GCValues)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c GCValues)
dataTypeOf :: GCValues -> DataType
$cdataTypeOf :: GCValues -> DataType
toConstr :: GCValues -> Constr
$ctoConstr :: GCValues -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GCValues
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GCValues
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GCValues -> c GCValues
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GCValues -> c GCValues
Data)

{-# LINE 85 "Graphics/X11/Xlib/Types.hsc" #-}

-- | pointer to an X11 @XSetWindowAttributes@ structure
newtype SetWindowAttributes = SetWindowAttributes (Ptr SetWindowAttributes)

{-# LINE 89 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (SetWindowAttributes -> SetWindowAttributes -> Bool
(SetWindowAttributes -> SetWindowAttributes -> Bool)
-> (SetWindowAttributes -> SetWindowAttributes -> Bool)
-> Eq SetWindowAttributes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetWindowAttributes -> SetWindowAttributes -> Bool
$c/= :: SetWindowAttributes -> SetWindowAttributes -> Bool
== :: SetWindowAttributes -> SetWindowAttributes -> Bool
$c== :: SetWindowAttributes -> SetWindowAttributes -> Bool
Eq, Eq SetWindowAttributes
Eq SetWindowAttributes
-> (SetWindowAttributes -> SetWindowAttributes -> Ordering)
-> (SetWindowAttributes -> SetWindowAttributes -> Bool)
-> (SetWindowAttributes -> SetWindowAttributes -> Bool)
-> (SetWindowAttributes -> SetWindowAttributes -> Bool)
-> (SetWindowAttributes -> SetWindowAttributes -> Bool)
-> (SetWindowAttributes
    -> SetWindowAttributes -> SetWindowAttributes)
-> (SetWindowAttributes
    -> SetWindowAttributes -> SetWindowAttributes)
-> Ord SetWindowAttributes
SetWindowAttributes -> SetWindowAttributes -> Bool
SetWindowAttributes -> SetWindowAttributes -> Ordering
SetWindowAttributes -> SetWindowAttributes -> SetWindowAttributes
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SetWindowAttributes -> SetWindowAttributes -> SetWindowAttributes
$cmin :: SetWindowAttributes -> SetWindowAttributes -> SetWindowAttributes
max :: SetWindowAttributes -> SetWindowAttributes -> SetWindowAttributes
$cmax :: SetWindowAttributes -> SetWindowAttributes -> SetWindowAttributes
>= :: SetWindowAttributes -> SetWindowAttributes -> Bool
$c>= :: SetWindowAttributes -> SetWindowAttributes -> Bool
> :: SetWindowAttributes -> SetWindowAttributes -> Bool
$c> :: SetWindowAttributes -> SetWindowAttributes -> Bool
<= :: SetWindowAttributes -> SetWindowAttributes -> Bool
$c<= :: SetWindowAttributes -> SetWindowAttributes -> Bool
< :: SetWindowAttributes -> SetWindowAttributes -> Bool
$c< :: SetWindowAttributes -> SetWindowAttributes -> Bool
compare :: SetWindowAttributes -> SetWindowAttributes -> Ordering
$ccompare :: SetWindowAttributes -> SetWindowAttributes -> Ordering
Ord, Int -> SetWindowAttributes -> ShowS
[SetWindowAttributes] -> ShowS
SetWindowAttributes -> String
(Int -> SetWindowAttributes -> ShowS)
-> (SetWindowAttributes -> String)
-> ([SetWindowAttributes] -> ShowS)
-> Show SetWindowAttributes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetWindowAttributes] -> ShowS
$cshowList :: [SetWindowAttributes] -> ShowS
show :: SetWindowAttributes -> String
$cshow :: SetWindowAttributes -> String
showsPrec :: Int -> SetWindowAttributes -> ShowS
$cshowsPrec :: Int -> SetWindowAttributes -> ShowS
Show, Typeable, Typeable SetWindowAttributes
Typeable SetWindowAttributes
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> SetWindowAttributes
    -> c SetWindowAttributes)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c SetWindowAttributes)
-> (SetWindowAttributes -> Constr)
-> (SetWindowAttributes -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c SetWindowAttributes))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c SetWindowAttributes))
-> ((forall b. Data b => b -> b)
    -> SetWindowAttributes -> SetWindowAttributes)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> SetWindowAttributes -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> SetWindowAttributes -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> SetWindowAttributes -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> SetWindowAttributes -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> SetWindowAttributes -> m SetWindowAttributes)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> SetWindowAttributes -> m SetWindowAttributes)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> SetWindowAttributes -> m SetWindowAttributes)
-> Data SetWindowAttributes
SetWindowAttributes -> DataType
SetWindowAttributes -> Constr
(forall b. Data b => b -> b)
-> SetWindowAttributes -> SetWindowAttributes
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> SetWindowAttributes -> u
forall u.
(forall d. Data d => d -> u) -> SetWindowAttributes -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SetWindowAttributes -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SetWindowAttributes -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SetWindowAttributes -> m SetWindowAttributes
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SetWindowAttributes -> m SetWindowAttributes
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SetWindowAttributes
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SetWindowAttributes
-> c SetWindowAttributes
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SetWindowAttributes)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SetWindowAttributes)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SetWindowAttributes -> m SetWindowAttributes
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SetWindowAttributes -> m SetWindowAttributes
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SetWindowAttributes -> m SetWindowAttributes
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SetWindowAttributes -> m SetWindowAttributes
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SetWindowAttributes -> m SetWindowAttributes
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SetWindowAttributes -> m SetWindowAttributes
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SetWindowAttributes -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SetWindowAttributes -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> SetWindowAttributes -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> SetWindowAttributes -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SetWindowAttributes -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SetWindowAttributes -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SetWindowAttributes -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SetWindowAttributes -> r
gmapT :: (forall b. Data b => b -> b)
-> SetWindowAttributes -> SetWindowAttributes
$cgmapT :: (forall b. Data b => b -> b)
-> SetWindowAttributes -> SetWindowAttributes
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SetWindowAttributes)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SetWindowAttributes)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SetWindowAttributes)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SetWindowAttributes)
dataTypeOf :: SetWindowAttributes -> DataType
$cdataTypeOf :: SetWindowAttributes -> DataType
toConstr :: SetWindowAttributes -> Constr
$ctoConstr :: SetWindowAttributes -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SetWindowAttributes
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SetWindowAttributes
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SetWindowAttributes
-> c SetWindowAttributes
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SetWindowAttributes
-> c SetWindowAttributes
Data)

{-# LINE 93 "Graphics/X11/Xlib/Types.hsc" #-}

-- | counterpart of an X11 @XVisualInfo@ structure
data VisualInfo = VisualInfo {
        VisualInfo -> Visual
visualInfo_visual :: Visual,
        VisualInfo -> VisualID
visualInfo_visualID :: VisualID,
        VisualInfo -> ScreenNumber
visualInfo_screen :: ScreenNumber,
        VisualInfo -> CInt
visualInfo_depth :: CInt,
        VisualInfo -> CInt
visualInfo_class :: CInt,
        VisualInfo -> CULong
visualInfo_redMask :: CULong,
        VisualInfo -> CULong
visualInfo_greenMask :: CULong,
        VisualInfo -> CULong
visualInfo_blueMask :: CULong,
        VisualInfo -> CInt
visualInfo_colormapSize :: CInt,
        VisualInfo -> CInt
visualInfo_bitsPerRGB :: CInt
        }

{-# LINE 108 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (VisualInfo -> VisualInfo -> Bool
(VisualInfo -> VisualInfo -> Bool)
-> (VisualInfo -> VisualInfo -> Bool) -> Eq VisualInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VisualInfo -> VisualInfo -> Bool
$c/= :: VisualInfo -> VisualInfo -> Bool
== :: VisualInfo -> VisualInfo -> Bool
$c== :: VisualInfo -> VisualInfo -> Bool
Eq, Int -> VisualInfo -> ShowS
[VisualInfo] -> ShowS
VisualInfo -> String
(Int -> VisualInfo -> ShowS)
-> (VisualInfo -> String)
-> ([VisualInfo] -> ShowS)
-> Show VisualInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VisualInfo] -> ShowS
$cshowList :: [VisualInfo] -> ShowS
show :: VisualInfo -> String
$cshow :: VisualInfo -> String
showsPrec :: Int -> VisualInfo -> ShowS
$cshowsPrec :: Int -> VisualInfo -> ShowS
Show, Typeable)

{-# LINE 112 "Graphics/X11/Xlib/Types.hsc" #-}

instance Default VisualInfo where
    def :: VisualInfo
def = VisualInfo :: Visual
-> VisualID
-> ScreenNumber
-> CInt
-> CInt
-> CULong
-> CULong
-> CULong
-> CInt
-> CInt
-> VisualInfo
VisualInfo {
        visualInfo_visual :: Visual
visualInfo_visual = Ptr Visual -> Visual
Visual Ptr Visual
forall a. Ptr a
nullPtr,
        visualInfo_visualID :: VisualID
visualInfo_visualID = VisualID
0,
        visualInfo_screen :: ScreenNumber
visualInfo_screen = ScreenNumber
0,
        visualInfo_depth :: CInt
visualInfo_depth = CInt
0,
        visualInfo_class :: CInt
visualInfo_class = CInt
0,
        visualInfo_redMask :: CULong
visualInfo_redMask = CULong
0,
        visualInfo_greenMask :: CULong
visualInfo_greenMask = CULong
0,
        visualInfo_blueMask :: CULong
visualInfo_blueMask = CULong
0,
        visualInfo_colormapSize :: CInt
visualInfo_colormapSize = CInt
0,
        visualInfo_bitsPerRGB :: CInt
visualInfo_bitsPerRGB = CInt
0
        }

instance Storable VisualInfo where
        sizeOf :: VisualInfo -> Int
sizeOf VisualInfo
_ = (Int
64)
{-# LINE 129 "Graphics/X11/Xlib/Types.hsc" #-}
        alignment :: VisualInfo -> Int
alignment VisualInfo
_ = CInt -> Int
forall a. Storable a => a -> Int
alignment (CInt
forall a. HasCallStack => a
undefined::CInt)
        peek :: Ptr VisualInfo -> IO VisualInfo
peek Ptr VisualInfo
p = do
                Visual
visual <- Ptr Visual -> Visual
Visual (Ptr Visual -> Visual) -> IO (Ptr Visual) -> IO Visual
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> IO (Ptr Visual)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VisualInfo
hsc_ptr Int
0) Ptr VisualInfo
p
{-# LINE 132 "Graphics/X11/Xlib/Types.hsc" #-}
                VisualID
visualID <- (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> IO VisualID
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VisualInfo
hsc_ptr Int
8) Ptr VisualInfo
p
{-# LINE 133 "Graphics/X11/Xlib/Types.hsc" #-}
                ScreenNumber
screen <- (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> IO ScreenNumber
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VisualInfo
hsc_ptr Int
16) Ptr VisualInfo
p
{-# LINE 134 "Graphics/X11/Xlib/Types.hsc" #-}
                CInt
depth <- (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VisualInfo
hsc_ptr Int
20) Ptr VisualInfo
p
{-# LINE 135 "Graphics/X11/Xlib/Types.hsc" #-}
                CInt
class_ <- (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VisualInfo
hsc_ptr Int
24) Ptr VisualInfo
p
{-# LINE 136 "Graphics/X11/Xlib/Types.hsc" #-}
                CULong
redMask <- (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> IO CULong
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VisualInfo
hsc_ptr Int
32) Ptr VisualInfo
p
{-# LINE 137 "Graphics/X11/Xlib/Types.hsc" #-}
                CULong
greenMask <- (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> IO CULong
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VisualInfo
hsc_ptr Int
40) Ptr VisualInfo
p
{-# LINE 138 "Graphics/X11/Xlib/Types.hsc" #-}
                CULong
blueMask <- (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> IO CULong
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VisualInfo
hsc_ptr Int
48) Ptr VisualInfo
p
{-# LINE 139 "Graphics/X11/Xlib/Types.hsc" #-}
                CInt
colormapSize <- (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VisualInfo
hsc_ptr Int
56) Ptr VisualInfo
p
{-# LINE 140 "Graphics/X11/Xlib/Types.hsc" #-}
                CInt
bitsPerRGB <- (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VisualInfo
hsc_ptr Int
60) Ptr VisualInfo
p
{-# LINE 141 "Graphics/X11/Xlib/Types.hsc" #-}
                VisualInfo -> IO VisualInfo
forall (m :: * -> *) a. Monad m => a -> m a
return (VisualInfo -> IO VisualInfo) -> VisualInfo -> IO VisualInfo
forall a b. (a -> b) -> a -> b
$ VisualInfo :: Visual
-> VisualID
-> ScreenNumber
-> CInt
-> CInt
-> CULong
-> CULong
-> CULong
-> CInt
-> CInt
-> VisualInfo
VisualInfo {
                        visualInfo_visual :: Visual
visualInfo_visual = Visual
visual,
                        visualInfo_visualID :: VisualID
visualInfo_visualID = VisualID
visualID,
                        visualInfo_screen :: ScreenNumber
visualInfo_screen = ScreenNumber
screen,
                        visualInfo_depth :: CInt
visualInfo_depth = CInt
depth,
                        visualInfo_class :: CInt
visualInfo_class = CInt
class_,
                        visualInfo_redMask :: CULong
visualInfo_redMask = CULong
redMask,
                        visualInfo_greenMask :: CULong
visualInfo_greenMask = CULong
greenMask,
                        visualInfo_blueMask :: CULong
visualInfo_blueMask = CULong
blueMask,
                        visualInfo_colormapSize :: CInt
visualInfo_colormapSize = CInt
colormapSize,
                        visualInfo_bitsPerRGB :: CInt
visualInfo_bitsPerRGB = CInt
bitsPerRGB
                        }
        poke :: Ptr VisualInfo -> VisualInfo -> IO ()
poke Ptr VisualInfo
p VisualInfo
info = do
                (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> Ptr Visual -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VisualInfo
hsc_ptr Int
0) Ptr VisualInfo
p Ptr Visual
visualPtr
{-# LINE 155 "Graphics/X11/Xlib/Types.hsc" #-}
                (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> VisualID -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VisualInfo
hsc_ptr Int
8) Ptr VisualInfo
p (VisualID -> IO ()) -> VisualID -> IO ()
forall a b. (a -> b) -> a -> b
$ VisualInfo -> VisualID
visualInfo_visualID VisualInfo
info
{-# LINE 156 "Graphics/X11/Xlib/Types.hsc" #-}
                (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> ScreenNumber -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VisualInfo
hsc_ptr Int
16) Ptr VisualInfo
p (ScreenNumber -> IO ()) -> ScreenNumber -> IO ()
forall a b. (a -> b) -> a -> b
$ VisualInfo -> ScreenNumber
visualInfo_screen VisualInfo
info
{-# LINE 157 "Graphics/X11/Xlib/Types.hsc" #-}
                (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VisualInfo
hsc_ptr Int
20) Ptr VisualInfo
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ VisualInfo -> CInt
visualInfo_depth VisualInfo
info
{-# LINE 158 "Graphics/X11/Xlib/Types.hsc" #-}
                (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VisualInfo
hsc_ptr Int
24) Ptr VisualInfo
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ VisualInfo -> CInt
visualInfo_class VisualInfo
info
{-# LINE 159 "Graphics/X11/Xlib/Types.hsc" #-}
                (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> CULong -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VisualInfo
hsc_ptr Int
32) Ptr VisualInfo
p (CULong -> IO ()) -> CULong -> IO ()
forall a b. (a -> b) -> a -> b
$ VisualInfo -> CULong
visualInfo_redMask VisualInfo
info
{-# LINE 160 "Graphics/X11/Xlib/Types.hsc" #-}
                (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> CULong -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VisualInfo
hsc_ptr Int
40) Ptr VisualInfo
p (CULong -> IO ()) -> CULong -> IO ()
forall a b. (a -> b) -> a -> b
$ VisualInfo -> CULong
visualInfo_greenMask VisualInfo
info
{-# LINE 161 "Graphics/X11/Xlib/Types.hsc" #-}
                (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> CULong -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VisualInfo
hsc_ptr Int
48) Ptr VisualInfo
p (CULong -> IO ()) -> CULong -> IO ()
forall a b. (a -> b) -> a -> b
$ VisualInfo -> CULong
visualInfo_blueMask VisualInfo
info
{-# LINE 162 "Graphics/X11/Xlib/Types.hsc" #-}
                (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VisualInfo
hsc_ptr Int
56) Ptr VisualInfo
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
{-# LINE 163 "Graphics/X11/Xlib/Types.hsc" #-}
                        VisualInfo -> CInt
visualInfo_colormapSize VisualInfo
info
                (\Ptr VisualInfo
hsc_ptr -> Ptr VisualInfo -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VisualInfo
hsc_ptr Int
60) Ptr VisualInfo
p (CInt -> IO ()) -> CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
{-# LINE 165 "Graphics/X11/Xlib/Types.hsc" #-}
                        VisualInfo -> CInt
visualInfo_bitsPerRGB VisualInfo
info
                where
                        ~(Visual Ptr Visual
visualPtr) = VisualInfo -> Visual
visualInfo_visual VisualInfo
info

-- | pointer to an X11 @XImage@ structure
newtype Image    = Image    (Ptr Image)

{-# LINE 172 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Image -> Image -> Bool
(Image -> Image -> Bool) -> (Image -> Image -> Bool) -> Eq Image
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Image -> Image -> Bool
$c/= :: Image -> Image -> Bool
== :: Image -> Image -> Bool
$c== :: Image -> Image -> Bool
Eq, Eq Image
Eq Image
-> (Image -> Image -> Ordering)
-> (Image -> Image -> Bool)
-> (Image -> Image -> Bool)
-> (Image -> Image -> Bool)
-> (Image -> Image -> Bool)
-> (Image -> Image -> Image)
-> (Image -> Image -> Image)
-> Ord Image
Image -> Image -> Bool
Image -> Image -> Ordering
Image -> Image -> Image
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Image -> Image -> Image
$cmin :: Image -> Image -> Image
max :: Image -> Image -> Image
$cmax :: Image -> Image -> Image
>= :: Image -> Image -> Bool
$c>= :: Image -> Image -> Bool
> :: Image -> Image -> Bool
$c> :: Image -> Image -> Bool
<= :: Image -> Image -> Bool
$c<= :: Image -> Image -> Bool
< :: Image -> Image -> Bool
$c< :: Image -> Image -> Bool
compare :: Image -> Image -> Ordering
$ccompare :: Image -> Image -> Ordering
Ord, Int -> Image -> ShowS
[Image] -> ShowS
Image -> String
(Int -> Image -> ShowS)
-> (Image -> String) -> ([Image] -> ShowS) -> Show Image
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Image] -> ShowS
$cshowList :: [Image] -> ShowS
show :: Image -> String
$cshow :: Image -> String
showsPrec :: Int -> Image -> ShowS
$cshowsPrec :: Int -> Image -> ShowS
Show, Typeable, Typeable Image
Typeable Image
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Image -> c Image)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Image)
-> (Image -> Constr)
-> (Image -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Image))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Image))
-> ((forall b. Data b => b -> b) -> Image -> Image)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r)
-> (forall u. (forall d. Data d => d -> u) -> Image -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Image -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Image -> m Image)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Image -> m Image)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Image -> m Image)
-> Data Image
Image -> DataType
Image -> Constr
(forall b. Data b => b -> b) -> Image -> Image
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Image -> u
forall u. (forall d. Data d => d -> u) -> Image -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Image -> m Image
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Image -> m Image
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Image
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Image -> c Image
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Image)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Image)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Image -> m Image
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Image -> m Image
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Image -> m Image
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Image -> m Image
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Image -> m Image
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Image -> m Image
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Image -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Image -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Image -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Image -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r
gmapT :: (forall b. Data b => b -> b) -> Image -> Image
$cgmapT :: (forall b. Data b => b -> b) -> Image -> Image
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Image)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Image)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Image)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Image)
dataTypeOf :: Image -> DataType
$cdataTypeOf :: Image -> DataType
toConstr :: Image -> Constr
$ctoConstr :: Image -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Image
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Image
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Image -> c Image
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Image -> c Image
Data)

{-# LINE 176 "Graphics/X11/Xlib/Types.hsc" #-}

type Pixel         = Word64
{-# LINE 178 "Graphics/X11/Xlib/Types.hsc" #-}
type Position      = Int32
{-# LINE 179 "Graphics/X11/Xlib/Types.hsc" #-}
type Dimension     = Word32
{-# LINE 180 "Graphics/X11/Xlib/Types.hsc" #-}
type Angle         = CInt
type ScreenNumber  = Word32
type Buffer        = CInt

----------------------------------------------------------------
-- Short forms used in structs
----------------------------------------------------------------

type ShortPosition = CShort
type ShortDimension = CUShort
type ShortAngle    = CShort

peekPositionField :: Ptr a -> CInt -> IO Position
peekPositionField :: forall a. Ptr a -> CInt -> IO Position
peekPositionField Ptr a
ptr CInt
off = do
        ShortPosition
v <- Ptr a -> Int -> IO ShortPosition
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr a
ptr (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
off)
        Position -> IO Position
forall (m :: * -> *) a. Monad m => a -> m a
return (ShortPosition -> Position
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ShortPosition
v::ShortPosition))

peekDimensionField :: Ptr a -> CInt -> IO Dimension
peekDimensionField :: forall a. Ptr a -> CInt -> IO ScreenNumber
peekDimensionField Ptr a
ptr CInt
off = do
        ShortDimension
v <- Ptr a -> Int -> IO ShortDimension
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr a
ptr (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
off)
        ScreenNumber -> IO ScreenNumber
forall (m :: * -> *) a. Monad m => a -> m a
return (ShortDimension -> ScreenNumber
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ShortDimension
v::ShortDimension))

peekAngleField :: Ptr a -> CInt -> IO Angle
peekAngleField :: forall a. Ptr a -> CInt -> IO CInt
peekAngleField Ptr a
ptr CInt
off = do
        ShortPosition
v <- Ptr a -> Int -> IO ShortPosition
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr a
ptr (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
off)
        CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return (ShortPosition -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ShortPosition
v::ShortAngle))

pokePositionField :: Ptr a -> CInt -> Position -> IO ()
pokePositionField :: forall a. Ptr a -> CInt -> Position -> IO ()
pokePositionField Ptr a
ptr CInt
off Position
v =
        Ptr a -> Int -> ShortPosition -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr a
ptr (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
off) (Position -> ShortPosition
forall a b. (Integral a, Num b) => a -> b
fromIntegral Position
v::ShortPosition)

pokeDimensionField :: Ptr a -> CInt -> Dimension -> IO ()
pokeDimensionField :: forall a. Ptr a -> CInt -> ScreenNumber -> IO ()
pokeDimensionField Ptr a
ptr CInt
off ScreenNumber
v =
        Ptr a -> Int -> ShortDimension -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr a
ptr (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
off) (ScreenNumber -> ShortDimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral ScreenNumber
v::ShortDimension)

pokeAngleField :: Ptr a -> CInt -> Angle -> IO ()
pokeAngleField :: forall a. Ptr a -> CInt -> CInt -> IO ()
pokeAngleField Ptr a
ptr CInt
off CInt
v =
        Ptr a -> Int -> ShortPosition -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr a
ptr (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
off) (CInt -> ShortPosition
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
v::ShortAngle)

----------------------------------------------------------------
-- Point
----------------------------------------------------------------

-- | counterpart of an X11 @XPoint@ structure
data Point = Point { Point -> Position
pt_x :: !Position, Point -> Position
pt_y :: !Position }

{-# LINE 226 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Point -> Point -> Bool
(Point -> Point -> Bool) -> (Point -> Point -> Bool) -> Eq Point
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Point -> Point -> Bool
$c/= :: Point -> Point -> Bool
== :: Point -> Point -> Bool
$c== :: Point -> Point -> Bool
Eq, Int -> Point -> ShowS
[Point] -> ShowS
Point -> String
(Int -> Point -> ShowS)
-> (Point -> String) -> ([Point] -> ShowS) -> Show Point
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Point] -> ShowS
$cshowList :: [Point] -> ShowS
show :: Point -> String
$cshow :: Point -> String
showsPrec :: Int -> Point -> ShowS
$cshowsPrec :: Int -> Point -> ShowS
Show, Typeable, Typeable Point
Typeable Point
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Point -> c Point)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Point)
-> (Point -> Constr)
-> (Point -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Point))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Point))
-> ((forall b. Data b => b -> b) -> Point -> Point)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Point -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Point -> r)
-> (forall u. (forall d. Data d => d -> u) -> Point -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Point -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Point -> m Point)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Point -> m Point)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Point -> m Point)
-> Data Point
Point -> DataType
Point -> Constr
(forall b. Data b => b -> b) -> Point -> Point
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Point -> u
forall u. (forall d. Data d => d -> u) -> Point -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Point -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Point -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Point -> m Point
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Point -> m Point
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Point
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Point -> c Point
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Point)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Point)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Point -> m Point
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Point -> m Point
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Point -> m Point
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Point -> m Point
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Point -> m Point
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Point -> m Point
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Point -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Point -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Point -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Point -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Point -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Point -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Point -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Point -> r
gmapT :: (forall b. Data b => b -> b) -> Point -> Point
$cgmapT :: (forall b. Data b => b -> b) -> Point -> Point
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Point)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Point)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Point)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Point)
dataTypeOf :: Point -> DataType
$cdataTypeOf :: Point -> DataType
toConstr :: Point -> Constr
$ctoConstr :: Point -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Point
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Point
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Point -> c Point
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Point -> c Point
Data)

{-# LINE 230 "Graphics/X11/Xlib/Types.hsc" #-}

instance Storable Point where
        sizeOf :: Point -> Int
sizeOf Point
_ = (Int
4)
{-# LINE 233 "Graphics/X11/Xlib/Types.hsc" #-}
        alignment :: Point -> Int
alignment Point
_ = CInt -> Int
forall a. Storable a => a -> Int
alignment (CInt
forall a. HasCallStack => a
undefined::CInt)
        peek :: Ptr Point -> IO Point
peek Ptr Point
p = do
                Position
x <- Ptr Point -> CInt -> IO Position
forall a. Ptr a -> CInt -> IO Position
peekPositionField Ptr Point
p (CInt
0)
{-# LINE 236 "Graphics/X11/Xlib/Types.hsc" #-}
                Position
y <- Ptr Point -> CInt -> IO Position
forall a. Ptr a -> CInt -> IO Position
peekPositionField Ptr Point
p (CInt
2)
{-# LINE 237 "Graphics/X11/Xlib/Types.hsc" #-}
                Point -> IO Point
forall (m :: * -> *) a. Monad m => a -> m a
return (Position -> Position -> Point
Point Position
x Position
y)
        poke :: Ptr Point -> Point -> IO ()
poke Ptr Point
p (Point Position
x Position
y) = do
                Ptr Point -> CInt -> Position -> IO ()
forall a. Ptr a -> CInt -> Position -> IO ()
pokePositionField Ptr Point
p (CInt
0) Position
x
{-# LINE 240 "Graphics/X11/Xlib/Types.hsc" #-}
                Ptr Point -> CInt -> Position -> IO ()
forall a. Ptr a -> CInt -> Position -> IO ()
pokePositionField Ptr Point
p (CInt
2) Position
y
{-# LINE 241 "Graphics/X11/Xlib/Types.hsc" #-}

----------------------------------------------------------------
-- Rectangle
----------------------------------------------------------------

-- | counterpart of an X11 @XRectangle@ structure
data Rectangle = Rectangle {
        Rectangle -> Position
rect_x      :: !Position,
        Rectangle -> Position
rect_y      :: !Position,
        Rectangle -> ScreenNumber
rect_width  :: !Dimension,
        Rectangle -> ScreenNumber
rect_height :: !Dimension
        }

{-# LINE 254 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Rectangle -> Rectangle -> Bool
(Rectangle -> Rectangle -> Bool)
-> (Rectangle -> Rectangle -> Bool) -> Eq Rectangle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Rectangle -> Rectangle -> Bool
$c/= :: Rectangle -> Rectangle -> Bool
== :: Rectangle -> Rectangle -> Bool
$c== :: Rectangle -> Rectangle -> Bool
Eq, ReadPrec [Rectangle]
ReadPrec Rectangle
Int -> ReadS Rectangle
ReadS [Rectangle]
(Int -> ReadS Rectangle)
-> ReadS [Rectangle]
-> ReadPrec Rectangle
-> ReadPrec [Rectangle]
-> Read Rectangle
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Rectangle]
$creadListPrec :: ReadPrec [Rectangle]
readPrec :: ReadPrec Rectangle
$creadPrec :: ReadPrec Rectangle
readList :: ReadS [Rectangle]
$creadList :: ReadS [Rectangle]
readsPrec :: Int -> ReadS Rectangle
$creadsPrec :: Int -> ReadS Rectangle
Read, Int -> Rectangle -> ShowS
[Rectangle] -> ShowS
Rectangle -> String
(Int -> Rectangle -> ShowS)
-> (Rectangle -> String)
-> ([Rectangle] -> ShowS)
-> Show Rectangle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Rectangle] -> ShowS
$cshowList :: [Rectangle] -> ShowS
show :: Rectangle -> String
$cshow :: Rectangle -> String
showsPrec :: Int -> Rectangle -> ShowS
$cshowsPrec :: Int -> Rectangle -> ShowS
Show, Typeable, Typeable Rectangle
Typeable Rectangle
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Rectangle -> c Rectangle)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Rectangle)
-> (Rectangle -> Constr)
-> (Rectangle -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Rectangle))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rectangle))
-> ((forall b. Data b => b -> b) -> Rectangle -> Rectangle)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Rectangle -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Rectangle -> r)
-> (forall u. (forall d. Data d => d -> u) -> Rectangle -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Rectangle -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Rectangle -> m Rectangle)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Rectangle -> m Rectangle)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Rectangle -> m Rectangle)
-> Data Rectangle
Rectangle -> DataType
Rectangle -> Constr
(forall b. Data b => b -> b) -> Rectangle -> Rectangle
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Rectangle -> u
forall u. (forall d. Data d => d -> u) -> Rectangle -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Rectangle -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Rectangle -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Rectangle -> m Rectangle
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rectangle -> m Rectangle
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Rectangle
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Rectangle -> c Rectangle
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Rectangle)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rectangle)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rectangle -> m Rectangle
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rectangle -> m Rectangle
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rectangle -> m Rectangle
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rectangle -> m Rectangle
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Rectangle -> m Rectangle
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Rectangle -> m Rectangle
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Rectangle -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Rectangle -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Rectangle -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Rectangle -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Rectangle -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Rectangle -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Rectangle -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Rectangle -> r
gmapT :: (forall b. Data b => b -> b) -> Rectangle -> Rectangle
$cgmapT :: (forall b. Data b => b -> b) -> Rectangle -> Rectangle
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rectangle)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rectangle)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Rectangle)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Rectangle)
dataTypeOf :: Rectangle -> DataType
$cdataTypeOf :: Rectangle -> DataType
toConstr :: Rectangle -> Constr
$ctoConstr :: Rectangle -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Rectangle
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Rectangle
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Rectangle -> c Rectangle
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Rectangle -> c Rectangle
Data)

{-# LINE 258 "Graphics/X11/Xlib/Types.hsc" #-}

instance Storable Rectangle where
        sizeOf :: Rectangle -> Int
sizeOf Rectangle
_ = (Int
8)
{-# LINE 261 "Graphics/X11/Xlib/Types.hsc" #-}
        alignment :: Rectangle -> Int
alignment Rectangle
_ = CInt -> Int
forall a. Storable a => a -> Int
alignment (CInt
forall a. HasCallStack => a
undefined::CInt)
        peek :: Ptr Rectangle -> IO Rectangle
peek Ptr Rectangle
p = do
                Position
x       <- Ptr Rectangle -> CInt -> IO Position
forall a. Ptr a -> CInt -> IO Position
peekPositionField Ptr Rectangle
p (CInt
0)
{-# LINE 264 "Graphics/X11/Xlib/Types.hsc" #-}
                Position
y       <- Ptr Rectangle -> CInt -> IO Position
forall a. Ptr a -> CInt -> IO Position
peekPositionField Ptr Rectangle
p (CInt
2)
{-# LINE 265 "Graphics/X11/Xlib/Types.hsc" #-}
                ScreenNumber
width   <- Ptr Rectangle -> CInt -> IO ScreenNumber
forall a. Ptr a -> CInt -> IO ScreenNumber
peekDimensionField Ptr Rectangle
p (CInt
4)
{-# LINE 266 "Graphics/X11/Xlib/Types.hsc" #-}
                ScreenNumber
height  <- Ptr Rectangle -> CInt -> IO ScreenNumber
forall a. Ptr a -> CInt -> IO ScreenNumber
peekDimensionField Ptr Rectangle
p (CInt
6)
{-# LINE 267 "Graphics/X11/Xlib/Types.hsc" #-}
                Rectangle -> IO Rectangle
forall (m :: * -> *) a. Monad m => a -> m a
return (Position -> Position -> ScreenNumber -> ScreenNumber -> Rectangle
Rectangle Position
x Position
y ScreenNumber
width ScreenNumber
height)
        poke :: Ptr Rectangle -> Rectangle -> IO ()
poke Ptr Rectangle
p (Rectangle Position
x Position
y ScreenNumber
width ScreenNumber
height) = do
                Ptr Rectangle -> CInt -> Position -> IO ()
forall a. Ptr a -> CInt -> Position -> IO ()
pokePositionField Ptr Rectangle
p (CInt
0) Position
x
{-# LINE 270 "Graphics/X11/Xlib/Types.hsc" #-}
                Ptr Rectangle -> CInt -> Position -> IO ()
forall a. Ptr a -> CInt -> Position -> IO ()
pokePositionField Ptr Rectangle
p (CInt
2) Position
y
{-# LINE 271 "Graphics/X11/Xlib/Types.hsc" #-}
                Ptr Rectangle -> CInt -> ScreenNumber -> IO ()
forall a. Ptr a -> CInt -> ScreenNumber -> IO ()
pokeDimensionField Ptr Rectangle
p (CInt
4) ScreenNumber
width
{-# LINE 272 "Graphics/X11/Xlib/Types.hsc" #-}
                Ptr Rectangle -> CInt -> ScreenNumber -> IO ()
forall a. Ptr a -> CInt -> ScreenNumber -> IO ()
pokeDimensionField Ptr Rectangle
p (CInt
6) ScreenNumber
height
{-# LINE 273 "Graphics/X11/Xlib/Types.hsc" #-}

----------------------------------------------------------------
-- Arc
----------------------------------------------------------------

-- | counterpart of an X11 @XArc@ structure
data Arc = Arc {
        Arc -> Position
arc_x :: Position,
        Arc -> Position
arc_y :: Position,
        Arc -> ScreenNumber
arc_width :: Dimension,
        Arc -> ScreenNumber
arc_height :: Dimension,
        Arc -> CInt
arc_angle1 :: Angle,
        Arc -> CInt
arc_angle2 :: Angle
        }

{-# LINE 288 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Arc -> Arc -> Bool
(Arc -> Arc -> Bool) -> (Arc -> Arc -> Bool) -> Eq Arc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Arc -> Arc -> Bool
$c/= :: Arc -> Arc -> Bool
== :: Arc -> Arc -> Bool
$c== :: Arc -> Arc -> Bool
Eq, Int -> Arc -> ShowS
[Arc] -> ShowS
Arc -> String
(Int -> Arc -> ShowS)
-> (Arc -> String) -> ([Arc] -> ShowS) -> Show Arc
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Arc] -> ShowS
$cshowList :: [Arc] -> ShowS
show :: Arc -> String
$cshow :: Arc -> String
showsPrec :: Int -> Arc -> ShowS
$cshowsPrec :: Int -> Arc -> ShowS
Show, Typeable)

{-# LINE 292 "Graphics/X11/Xlib/Types.hsc" #-}

instance Storable Arc where
        sizeOf :: Arc -> Int
sizeOf Arc
_ = (Int
12)
{-# LINE 295 "Graphics/X11/Xlib/Types.hsc" #-}
        alignment :: Arc -> Int
alignment Arc
_ = CInt -> Int
forall a. Storable a => a -> Int
alignment (CInt
forall a. HasCallStack => a
undefined::CInt)
        peek :: Ptr Arc -> IO Arc
peek Ptr Arc
p = do
                Position
x       <- Ptr Arc -> CInt -> IO Position
forall a. Ptr a -> CInt -> IO Position
peekPositionField Ptr Arc
p (CInt
0)
{-# LINE 298 "Graphics/X11/Xlib/Types.hsc" #-}
                Position
y       <- Ptr Arc -> CInt -> IO Position
forall a. Ptr a -> CInt -> IO Position
peekPositionField Ptr Arc
p (CInt
2)
{-# LINE 299 "Graphics/X11/Xlib/Types.hsc" #-}
                ScreenNumber
width   <- Ptr Arc -> CInt -> IO ScreenNumber
forall a. Ptr a -> CInt -> IO ScreenNumber
peekDimensionField Ptr Arc
p (CInt
4)
{-# LINE 300 "Graphics/X11/Xlib/Types.hsc" #-}
                ScreenNumber
height  <- Ptr Arc -> CInt -> IO ScreenNumber
forall a. Ptr a -> CInt -> IO ScreenNumber
peekDimensionField Ptr Arc
p (CInt
6)
{-# LINE 301 "Graphics/X11/Xlib/Types.hsc" #-}
                CInt
angle1  <- Ptr Arc -> CInt -> IO CInt
forall a. Ptr a -> CInt -> IO CInt
peekAngleField Ptr Arc
p (CInt
8)
{-# LINE 302 "Graphics/X11/Xlib/Types.hsc" #-}
                CInt
angle2  <- Ptr Arc -> CInt -> IO CInt
forall a. Ptr a -> CInt -> IO CInt
peekAngleField Ptr Arc
p (CInt
10)
{-# LINE 303 "Graphics/X11/Xlib/Types.hsc" #-}
                Arc -> IO Arc
forall (m :: * -> *) a. Monad m => a -> m a
return (Position
-> Position -> ScreenNumber -> ScreenNumber -> CInt -> CInt -> Arc
Arc Position
x Position
y ScreenNumber
width ScreenNumber
height CInt
angle1 CInt
angle2)
        poke :: Ptr Arc -> Arc -> IO ()
poke Ptr Arc
p (Arc Position
x Position
y ScreenNumber
width ScreenNumber
height CInt
angle1 CInt
angle2) = do
                Ptr Arc -> CInt -> Position -> IO ()
forall a. Ptr a -> CInt -> Position -> IO ()
pokePositionField Ptr Arc
p (CInt
0) Position
x
{-# LINE 306 "Graphics/X11/Xlib/Types.hsc" #-}
                Ptr Arc -> CInt -> Position -> IO ()
forall a. Ptr a -> CInt -> Position -> IO ()
pokePositionField Ptr Arc
p (CInt
2) Position
y
{-# LINE 307 "Graphics/X11/Xlib/Types.hsc" #-}
                Ptr Arc -> CInt -> ScreenNumber -> IO ()
forall a. Ptr a -> CInt -> ScreenNumber -> IO ()
pokeDimensionField Ptr Arc
p (CInt
4) ScreenNumber
width
{-# LINE 308 "Graphics/X11/Xlib/Types.hsc" #-}
                Ptr Arc -> CInt -> ScreenNumber -> IO ()
forall a. Ptr a -> CInt -> ScreenNumber -> IO ()
pokeDimensionField Ptr Arc
p (CInt
6) ScreenNumber
height
{-# LINE 309 "Graphics/X11/Xlib/Types.hsc" #-}
                Ptr Arc -> CInt -> CInt -> IO ()
forall a. Ptr a -> CInt -> CInt -> IO ()
pokeAngleField Ptr Arc
p (CInt
8) CInt
angle1
{-# LINE 310 "Graphics/X11/Xlib/Types.hsc" #-}
                Ptr Arc -> CInt -> CInt -> IO ()
forall a. Ptr a -> CInt -> CInt -> IO ()
pokeAngleField Ptr Arc
p (CInt
10) CInt
angle2
{-# LINE 311 "Graphics/X11/Xlib/Types.hsc" #-}

----------------------------------------------------------------
-- Segment
----------------------------------------------------------------

-- | counterpart of an X11 @XSegment@ structure
data Segment = Segment {
        Segment -> Position
seg_x1 :: Position,
        Segment -> Position
seg_y1 :: Position,
        Segment -> Position
seg_x2 :: Position,
        Segment -> Position
seg_y2 :: Position
        }

{-# LINE 324 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Segment -> Segment -> Bool
(Segment -> Segment -> Bool)
-> (Segment -> Segment -> Bool) -> Eq Segment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Segment -> Segment -> Bool
$c/= :: Segment -> Segment -> Bool
== :: Segment -> Segment -> Bool
$c== :: Segment -> Segment -> Bool
Eq, Int -> Segment -> ShowS
[Segment] -> ShowS
Segment -> String
(Int -> Segment -> ShowS)
-> (Segment -> String) -> ([Segment] -> ShowS) -> Show Segment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Segment] -> ShowS
$cshowList :: [Segment] -> ShowS
show :: Segment -> String
$cshow :: Segment -> String
showsPrec :: Int -> Segment -> ShowS
$cshowsPrec :: Int -> Segment -> ShowS
Show, Typeable, Typeable Segment
Typeable Segment
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Segment -> c Segment)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Segment)
-> (Segment -> Constr)
-> (Segment -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Segment))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Segment))
-> ((forall b. Data b => b -> b) -> Segment -> Segment)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Segment -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Segment -> r)
-> (forall u. (forall d. Data d => d -> u) -> Segment -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Segment -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Segment -> m Segment)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Segment -> m Segment)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Segment -> m Segment)
-> Data Segment
Segment -> DataType
Segment -> Constr
(forall b. Data b => b -> b) -> Segment -> Segment
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Segment -> u
forall u. (forall d. Data d => d -> u) -> Segment -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Segment -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Segment -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Segment -> m Segment
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Segment -> m Segment
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Segment
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Segment -> c Segment
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Segment)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Segment)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Segment -> m Segment
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Segment -> m Segment
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Segment -> m Segment
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Segment -> m Segment
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Segment -> m Segment
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Segment -> m Segment
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Segment -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Segment -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Segment -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Segment -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Segment -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Segment -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Segment -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Segment -> r
gmapT :: (forall b. Data b => b -> b) -> Segment -> Segment
$cgmapT :: (forall b. Data b => b -> b) -> Segment -> Segment
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Segment)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Segment)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Segment)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Segment)
dataTypeOf :: Segment -> DataType
$cdataTypeOf :: Segment -> DataType
toConstr :: Segment -> Constr
$ctoConstr :: Segment -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Segment
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Segment
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Segment -> c Segment
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Segment -> c Segment
Data)

{-# LINE 328 "Graphics/X11/Xlib/Types.hsc" #-}

instance Storable Segment where
        sizeOf :: Segment -> Int
sizeOf Segment
_ = (Int
8)
{-# LINE 331 "Graphics/X11/Xlib/Types.hsc" #-}
        alignment :: Segment -> Int
alignment Segment
_ = CInt -> Int
forall a. Storable a => a -> Int
alignment (CInt
forall a. HasCallStack => a
undefined::CInt)
        peek :: Ptr Segment -> IO Segment
peek Ptr Segment
p = do
                Position
x1 <- Ptr Segment -> CInt -> IO Position
forall a. Ptr a -> CInt -> IO Position
peekPositionField Ptr Segment
p (CInt
0)
{-# LINE 334 "Graphics/X11/Xlib/Types.hsc" #-}
                Position
y1 <- Ptr Segment -> CInt -> IO Position
forall a. Ptr a -> CInt -> IO Position
peekPositionField Ptr Segment
p (CInt
2)
{-# LINE 335 "Graphics/X11/Xlib/Types.hsc" #-}
                Position
x2 <- Ptr Segment -> CInt -> IO Position
forall a. Ptr a -> CInt -> IO Position
peekPositionField Ptr Segment
p (CInt
4)
{-# LINE 336 "Graphics/X11/Xlib/Types.hsc" #-}
                Position
y2 <- Ptr Segment -> CInt -> IO Position
forall a. Ptr a -> CInt -> IO Position
peekPositionField Ptr Segment
p (CInt
6)
{-# LINE 337 "Graphics/X11/Xlib/Types.hsc" #-}
                Segment -> IO Segment
forall (m :: * -> *) a. Monad m => a -> m a
return (Position -> Position -> Position -> Position -> Segment
Segment Position
x1 Position
y1 Position
x2 Position
y2)
        poke :: Ptr Segment -> Segment -> IO ()
poke Ptr Segment
p (Segment Position
x1 Position
y1 Position
x2 Position
y2) = do
                Ptr Segment -> CInt -> Position -> IO ()
forall a. Ptr a -> CInt -> Position -> IO ()
pokePositionField Ptr Segment
p (CInt
0) Position
x1
{-# LINE 340 "Graphics/X11/Xlib/Types.hsc" #-}
                Ptr Segment -> CInt -> Position -> IO ()
forall a. Ptr a -> CInt -> Position -> IO ()
pokePositionField Ptr Segment
p (CInt
2) Position
y1
{-# LINE 341 "Graphics/X11/Xlib/Types.hsc" #-}
                Ptr Segment -> CInt -> Position -> IO ()
forall a. Ptr a -> CInt -> Position -> IO ()
pokePositionField Ptr Segment
p (CInt
4) Position
x2
{-# LINE 342 "Graphics/X11/Xlib/Types.hsc" #-}
                Ptr Segment -> CInt -> Position -> IO ()
forall a. Ptr a -> CInt -> Position -> IO ()
pokePositionField Ptr Segment
p (CInt
6) Position
y2
{-# LINE 343 "Graphics/X11/Xlib/Types.hsc" #-}

----------------------------------------------------------------
-- Color
----------------------------------------------------------------

-- | counterpart of an X11 @XColor@ structure
data Color = Color {
        Color -> VisualID
color_pixel :: Pixel,
        Color -> Word16
color_red :: Word16,
        Color -> Word16
color_green :: Word16,
        Color -> Word16
color_blue :: Word16,
        Color -> Word8
color_flags :: Word8
        }

{-# LINE 357 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Color -> Color -> Bool
(Color -> Color -> Bool) -> (Color -> Color -> Bool) -> Eq Color
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Color -> Color -> Bool
$c/= :: Color -> Color -> Bool
== :: Color -> Color -> Bool
$c== :: Color -> Color -> Bool
Eq, Int -> Color -> ShowS
[Color] -> ShowS
Color -> String
(Int -> Color -> ShowS)
-> (Color -> String) -> ([Color] -> ShowS) -> Show Color
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Color] -> ShowS
$cshowList :: [Color] -> ShowS
show :: Color -> String
$cshow :: Color -> String
showsPrec :: Int -> Color -> ShowS
$cshowsPrec :: Int -> Color -> ShowS
Show, Typeable, Typeable Color
Typeable Color
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Color -> c Color)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Color)
-> (Color -> Constr)
-> (Color -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Color))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Color))
-> ((forall b. Data b => b -> b) -> Color -> Color)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r)
-> (forall u. (forall d. Data d => d -> u) -> Color -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Color -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Color -> m Color)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Color -> m Color)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Color -> m Color)
-> Data Color
Color -> DataType
Color -> Constr
(forall b. Data b => b -> b) -> Color -> Color
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Color -> u
forall u. (forall d. Data d => d -> u) -> Color -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Color -> m Color
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Color -> m Color
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Color
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Color -> c Color
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Color)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Color)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Color -> m Color
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Color -> m Color
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Color -> m Color
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Color -> m Color
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Color -> m Color
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Color -> m Color
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Color -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Color -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Color -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Color -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r
gmapT :: (forall b. Data b => b -> b) -> Color -> Color
$cgmapT :: (forall b. Data b => b -> b) -> Color -> Color
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Color)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Color)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Color)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Color)
dataTypeOf :: Color -> DataType
$cdataTypeOf :: Color -> DataType
toConstr :: Color -> Constr
$ctoConstr :: Color -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Color
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Color
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Color -> c Color
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Color -> c Color
Data)

{-# LINE 361 "Graphics/X11/Xlib/Types.hsc" #-}

instance Storable Color where
        sizeOf :: Color -> Int
sizeOf Color
_ = (Int
16)
{-# LINE 364 "Graphics/X11/Xlib/Types.hsc" #-}
        alignment :: Color -> Int
alignment Color
_ = CInt -> Int
forall a. Storable a => a -> Int
alignment (CInt
forall a. HasCallStack => a
undefined::CInt)
        peek :: Ptr Color -> IO Color
peek Ptr Color
p = do
                VisualID
pixel   <- (\Ptr Color
hsc_ptr -> Ptr Color -> Int -> IO VisualID
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Color
hsc_ptr Int
0) Ptr Color
p
{-# LINE 367 "Graphics/X11/Xlib/Types.hsc" #-}
                Word16
red     <- (\Ptr Color
hsc_ptr -> Ptr Color -> Int -> IO Word16
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Color
hsc_ptr Int
8)   Ptr Color
p
{-# LINE 368 "Graphics/X11/Xlib/Types.hsc" #-}
                Word16
green   <- (\Ptr Color
hsc_ptr -> Ptr Color -> Int -> IO Word16
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Color
hsc_ptr Int
10) Ptr Color
p
{-# LINE 369 "Graphics/X11/Xlib/Types.hsc" #-}
                Word16
blue    <- (\Ptr Color
hsc_ptr -> Ptr Color -> Int -> IO Word16
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Color
hsc_ptr Int
12)  Ptr Color
p
{-# LINE 370 "Graphics/X11/Xlib/Types.hsc" #-}
                Word8
flags   <- (\Ptr Color
hsc_ptr -> Ptr Color -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Color
hsc_ptr Int
14) Ptr Color
p
{-# LINE 371 "Graphics/X11/Xlib/Types.hsc" #-}
                Color -> IO Color
forall (m :: * -> *) a. Monad m => a -> m a
return (VisualID -> Word16 -> Word16 -> Word16 -> Word8 -> Color
Color VisualID
pixel Word16
red Word16
green Word16
blue Word8
flags)
        poke :: Ptr Color -> Color -> IO ()
poke Ptr Color
p (Color VisualID
pixel Word16
red Word16
green Word16
blue Word8
flags) = do
                (\Ptr Color
hsc_ptr -> Ptr Color -> Int -> VisualID -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Color
hsc_ptr Int
0)    Ptr Color
p VisualID
pixel
{-# LINE 374 "Graphics/X11/Xlib/Types.hsc" #-}
                (\Ptr Color
hsc_ptr -> Ptr Color -> Int -> Word16 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Color
hsc_ptr Int
8)      Ptr Color
p Word16
red
{-# LINE 375 "Graphics/X11/Xlib/Types.hsc" #-}
                (\Ptr Color
hsc_ptr -> Ptr Color -> Int -> Word16 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Color
hsc_ptr Int
10)    Ptr Color
p Word16
green
{-# LINE 376 "Graphics/X11/Xlib/Types.hsc" #-}
                (\Ptr Color
hsc_ptr -> Ptr Color -> Int -> Word16 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Color
hsc_ptr Int
12)     Ptr Color
p Word16
blue
{-# LINE 377 "Graphics/X11/Xlib/Types.hsc" #-}
                (\Ptr Color
hsc_ptr -> Ptr Color -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Color
hsc_ptr Int
14)    Ptr Color
p Word8
flags
{-# LINE 378 "Graphics/X11/Xlib/Types.hsc" #-}

----------------------------------------------------------------
-- End
----------------------------------------------------------------