{-# INCLUDE "HsXlib.h" #-}
{-# LINE 1 "Graphics/X11/Xlib/Types.hsc" #-}
{-# OPTIONS_GHC -fglasgow-exts #-}
{-# LINE 2 "Graphics/X11/Xlib/Types.hsc" #-}
-----------------------------------------------------------------------------
-- |
-- 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,
        Image(..), Point(..), Rectangle(..), Arc(..), Segment(..), Color(..),
        Pixel, Position, Dimension, Angle, ScreenNumber, Buffer
        ) where

-- 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 32 "Graphics/X11/Xlib/Types.hsc" #-}
import Data.Generics

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


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

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

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

{-# LINE 44 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Eq, Ord, Show, Typeable, Data)

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

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

{-# LINE 52 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Eq, Ord, Show, Typeable, Data)

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

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

{-# LINE 60 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Eq, Ord, Show, Typeable, Data)

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

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

{-# LINE 68 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Eq, Ord, Show, Typeable, Data)

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

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

{-# LINE 76 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Eq, Ord, Show, Typeable, Data)

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

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

{-# LINE 84 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Eq, Ord, Show, Typeable, Data)

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

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

{-# LINE 92 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Eq, Ord, Show, Typeable, Data)

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

type Pixel         = Word32
{-# LINE 98 "Graphics/X11/Xlib/Types.hsc" #-}
type Position      = Int32
{-# LINE 99 "Graphics/X11/Xlib/Types.hsc" #-}
type Dimension     = Word32
{-# LINE 100 "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 ptr off = do
        v <- peekByteOff ptr (fromIntegral off)
        return (fromIntegral (v::ShortPosition))

peekDimensionField :: Ptr a -> CInt -> IO Dimension
peekDimensionField ptr off = do
        v <- peekByteOff ptr (fromIntegral off)
        return (fromIntegral (v::ShortDimension))

peekAngleField :: Ptr a -> CInt -> IO Angle
peekAngleField ptr off = do
        v <- peekByteOff ptr (fromIntegral off)
        return (fromIntegral (v::ShortAngle))

pokePositionField :: Ptr a -> CInt -> Position -> IO ()
pokePositionField ptr off v =
        pokeByteOff ptr (fromIntegral off) (fromIntegral v::ShortPosition)

pokeDimensionField :: Ptr a -> CInt -> Dimension -> IO ()
pokeDimensionField ptr off v =
        pokeByteOff ptr (fromIntegral off) (fromIntegral v::ShortDimension)

pokeAngleField :: Ptr a -> CInt -> Angle -> IO ()
pokeAngleField ptr off v =
        pokeByteOff ptr (fromIntegral off) (fromIntegral v::ShortAngle)

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

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

{-# LINE 146 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Eq, Show, Typeable, Data)

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

instance Storable Point where
        sizeOf _ = (4)
{-# LINE 153 "Graphics/X11/Xlib/Types.hsc" #-}
        alignment _ = alignment (undefined::CInt)
        peek p = do
                x <- peekPositionField p (0)
{-# LINE 156 "Graphics/X11/Xlib/Types.hsc" #-}
                y <- peekPositionField p (2)
{-# LINE 157 "Graphics/X11/Xlib/Types.hsc" #-}
                return (Point x y)
        poke p (Point x y) = do
                pokePositionField p (0) x
{-# LINE 160 "Graphics/X11/Xlib/Types.hsc" #-}
                pokePositionField p (2) y
{-# LINE 161 "Graphics/X11/Xlib/Types.hsc" #-}

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

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

{-# LINE 174 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Eq, Show, Typeable, Data)

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

instance Storable Rectangle where
        sizeOf _ = (8)
{-# LINE 181 "Graphics/X11/Xlib/Types.hsc" #-}
        alignment _ = alignment (undefined::CInt)
        peek p = do
                x       <- peekPositionField p (0)
{-# LINE 184 "Graphics/X11/Xlib/Types.hsc" #-}
                y       <- peekPositionField p (2)
{-# LINE 185 "Graphics/X11/Xlib/Types.hsc" #-}
                width   <- peekDimensionField p (4)
{-# LINE 186 "Graphics/X11/Xlib/Types.hsc" #-}
                height  <- peekDimensionField p (6)
{-# LINE 187 "Graphics/X11/Xlib/Types.hsc" #-}
                return (Rectangle x y width height)
        poke p (Rectangle x y width height) = do
                pokePositionField p (0) x
{-# LINE 190 "Graphics/X11/Xlib/Types.hsc" #-}
                pokePositionField p (2) y
{-# LINE 191 "Graphics/X11/Xlib/Types.hsc" #-}
                pokeDimensionField p (4) width
{-# LINE 192 "Graphics/X11/Xlib/Types.hsc" #-}
                pokeDimensionField p (6) height
{-# LINE 193 "Graphics/X11/Xlib/Types.hsc" #-}

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

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

{-# LINE 208 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Eq, Show, Typeable)

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

instance Storable Arc where
        sizeOf _ = (12)
{-# LINE 215 "Graphics/X11/Xlib/Types.hsc" #-}
        alignment _ = alignment (undefined::CInt)
        peek p = do
                x       <- peekPositionField p (0)
{-# LINE 218 "Graphics/X11/Xlib/Types.hsc" #-}
                y       <- peekPositionField p (2)
{-# LINE 219 "Graphics/X11/Xlib/Types.hsc" #-}
                width   <- peekDimensionField p (4)
{-# LINE 220 "Graphics/X11/Xlib/Types.hsc" #-}
                height  <- peekDimensionField p (6)
{-# LINE 221 "Graphics/X11/Xlib/Types.hsc" #-}
                angle1  <- peekAngleField p (8)
{-# LINE 222 "Graphics/X11/Xlib/Types.hsc" #-}
                angle2  <- peekAngleField p (10)
{-# LINE 223 "Graphics/X11/Xlib/Types.hsc" #-}
                return (Arc x y width height angle1 angle2)
        poke p (Arc x y width height angle1 angle2) = do
                pokePositionField p (0) x
{-# LINE 226 "Graphics/X11/Xlib/Types.hsc" #-}
                pokePositionField p (2) y
{-# LINE 227 "Graphics/X11/Xlib/Types.hsc" #-}
                pokeDimensionField p (4) width
{-# LINE 228 "Graphics/X11/Xlib/Types.hsc" #-}
                pokeDimensionField p (6) height
{-# LINE 229 "Graphics/X11/Xlib/Types.hsc" #-}
                pokeAngleField p (8) angle1
{-# LINE 230 "Graphics/X11/Xlib/Types.hsc" #-}
                pokeAngleField p (10) angle2
{-# LINE 231 "Graphics/X11/Xlib/Types.hsc" #-}

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

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

{-# LINE 244 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Eq, Show, Typeable, Data)

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

instance Storable Segment where
        sizeOf _ = (8)
{-# LINE 251 "Graphics/X11/Xlib/Types.hsc" #-}
        alignment _ = alignment (undefined::CInt)
        peek p = do
                x1 <- peekPositionField p (0)
{-# LINE 254 "Graphics/X11/Xlib/Types.hsc" #-}
                y1 <- peekPositionField p (2)
{-# LINE 255 "Graphics/X11/Xlib/Types.hsc" #-}
                x2 <- peekPositionField p (4)
{-# LINE 256 "Graphics/X11/Xlib/Types.hsc" #-}
                y2 <- peekPositionField p (6)
{-# LINE 257 "Graphics/X11/Xlib/Types.hsc" #-}
                return (Segment x1 y1 x2 y2)
        poke p (Segment x1 y1 x2 y2) = do
                pokePositionField p (0) x1
{-# LINE 260 "Graphics/X11/Xlib/Types.hsc" #-}
                pokePositionField p (2) y1
{-# LINE 261 "Graphics/X11/Xlib/Types.hsc" #-}
                pokePositionField p (4) x2
{-# LINE 262 "Graphics/X11/Xlib/Types.hsc" #-}
                pokePositionField p (6) y2
{-# LINE 263 "Graphics/X11/Xlib/Types.hsc" #-}

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

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

{-# LINE 277 "Graphics/X11/Xlib/Types.hsc" #-}
        deriving (Eq, Show, Typeable, Data)

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

instance Storable Color where
        sizeOf _ = (12)
{-# LINE 284 "Graphics/X11/Xlib/Types.hsc" #-}
        alignment _ = alignment (undefined::CInt)
        peek p = do
                pixel   <- (\hsc_ptr -> peekByteOff hsc_ptr 0) p
{-# LINE 287 "Graphics/X11/Xlib/Types.hsc" #-}
                red     <- (\hsc_ptr -> peekByteOff hsc_ptr 4)   p
{-# LINE 288 "Graphics/X11/Xlib/Types.hsc" #-}
                green   <- (\hsc_ptr -> peekByteOff hsc_ptr 6) p
{-# LINE 289 "Graphics/X11/Xlib/Types.hsc" #-}
                blue    <- (\hsc_ptr -> peekByteOff hsc_ptr 8)  p
{-# LINE 290 "Graphics/X11/Xlib/Types.hsc" #-}
                flags   <- (\hsc_ptr -> peekByteOff hsc_ptr 10) p
{-# LINE 291 "Graphics/X11/Xlib/Types.hsc" #-}
                return (Color pixel red green blue flags)
        poke p (Color pixel red green blue flags) = do
                (\hsc_ptr -> pokeByteOff hsc_ptr 0)    p pixel
{-# LINE 294 "Graphics/X11/Xlib/Types.hsc" #-}
                (\hsc_ptr -> pokeByteOff hsc_ptr 4)      p red
{-# LINE 295 "Graphics/X11/Xlib/Types.hsc" #-}
                (\hsc_ptr -> pokeByteOff hsc_ptr 6)    p green
{-# LINE 296 "Graphics/X11/Xlib/Types.hsc" #-}
                (\hsc_ptr -> pokeByteOff hsc_ptr 8)     p blue
{-# LINE 297 "Graphics/X11/Xlib/Types.hsc" #-}
                (\hsc_ptr -> pokeByteOff hsc_ptr 10)    p flags
{-# LINE 298 "Graphics/X11/Xlib/Types.hsc" #-}

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