|
Graphics.X11.Xlib.Types | Portability | portable | Stability | provisional | Maintainer | libraries@haskell.org |
|
|
|
|
|
Description |
A collection of type declarations for interfacing with Xlib.
|
|
Synopsis |
|
newtype Display = Display (Ptr Display) | | newtype Screen = Screen (Ptr Screen) | | newtype Visual = Visual (Ptr Visual) | | newtype FontStruct = FontStruct (Ptr FontStruct) | | newtype GC = GC (Ptr GC) | | newtype XGCValues = XGCValues (Ptr XGCValues) | | newtype XSetWindowAttributes = XSetWindowAttributes XSetWindowAttributesPtr | | type XSetWindowAttributesPtr = Ptr XSetWindowAttributes | | type Pixel = Word32 | | type Position = Int32 | | type Dimension = Word32 | | type Angle = Int | | type ScreenNumber = Word32 | | type Byte = Word8 | | type Buffer = Int | | type ShortPosition = Int16 | | type ShortDimension = Word16 | | type ShortAngle = Int16 | | type Short = Int16 | | peekPositionField :: Ptr a -> Int -> IO Position | | peekDimensionField :: Ptr a -> Int -> IO Dimension | | peekAngleField :: Ptr a -> Int -> IO Angle | | pokePositionField :: Ptr a -> Int -> Position -> IO () | | pokeDimensionField :: Ptr a -> Int -> Dimension -> IO () | | pokeAngleField :: Ptr a -> Int -> Angle -> IO () | | data Storable' a = Storable' {} | | alloca' :: Storable' a -> (Ptr a -> IO b) -> IO b | | withStorable' :: Storable' a -> a -> (Ptr a -> IO b) -> IO b | | peekElemOff' :: Storable' a -> Ptr a -> Int -> IO a | | pokeElemOff' :: Storable' a -> Ptr a -> Int -> a -> IO () | | peekArray' :: Storable' a -> Int -> Ptr a -> IO [a] | | pokeArray' :: Storable' a -> Ptr a -> [a] -> IO () | | withArray' :: Storable' a -> [a] -> (Ptr a -> Int -> IO b) -> IO b | | type Point = (Position, Position) | | s_Point :: Storable' Point | | peekPoint :: Ptr Point -> IO Point | | pokePoint :: Ptr Point -> Point -> IO () | | peekPointArray :: Int -> Ptr Point -> IO [Point] | | withPointArray :: [Point] -> (Ptr Point -> Int -> IO b) -> IO b | | type Rectangle = (Position, Position, Dimension, Dimension) | | s_Rectangle :: Storable' Rectangle | | peekRectangle :: Ptr Rectangle -> IO Rectangle | | pokeRectangle :: Ptr Rectangle -> Rectangle -> IO () | | allocaRectangle :: (Ptr Rectangle -> IO a) -> IO a | | withRectangle :: Rectangle -> (Ptr Rectangle -> IO a) -> IO a | | peekRectangleArray :: Int -> Ptr Rectangle -> IO [Rectangle] | | withRectangleArray :: [Rectangle] -> (Ptr Rectangle -> Int -> IO b) -> IO b | | type Arc = (Position, Position, Dimension, Dimension, Angle, Angle) | | s_Arc :: Storable' Arc | | peekArc :: Ptr Arc -> IO Arc | | pokeArc :: Ptr Arc -> Arc -> IO () | | peekArcArray :: Int -> Ptr Arc -> IO [Arc] | | withArcArray :: [Arc] -> (Ptr Arc -> Int -> IO b) -> IO b | | type Segment = (Position, Position, Position, Position) | | s_Segment :: Storable' Segment | | peekSegment :: Ptr Segment -> IO Segment | | pokeSegment :: Ptr Segment -> Segment -> IO () | | peekSegmentArray :: Int -> Ptr Segment -> IO [Segment] | | withSegmentArray :: [Segment] -> (Ptr Segment -> Int -> IO b) -> IO b | | type Color = (Pixel, Word16, Word16, Word16, Word8) | | s_Color :: Storable' Color | | peekColor :: Ptr Color -> IO Color | | pokeColor :: Ptr Color -> Color -> IO () | | allocaColor :: (Ptr Color -> IO a) -> IO a | | withColor :: Color -> (Ptr Color -> IO a) -> IO a | | peekColorArray :: Int -> Ptr Color -> IO [Color] | | withColorArray :: [Color] -> (Ptr Color -> Int -> IO b) -> IO b | | type ListPoint = [Point] | | type ListRectangle = [Rectangle] | | type ListArc = [Arc] | | type ListSegment = [Segment] | | type ListColor = [Color] |
|
|
Documentation |
|
newtype Display |
pointer to an X11 Display structure
| Constructors | |
|
|
newtype Screen |
pointer to an X11 Screen structure
| Constructors | |
|
|
newtype Visual |
pointer to an X11 Visual structure
| Constructors | |
|
|
newtype FontStruct |
pointer to an X11 XFontStruct structure
| Constructors | |
|
|
newtype GC |
|
|
newtype XGCValues |
|
|
newtype XSetWindowAttributes |
|
|
type XSetWindowAttributesPtr = Ptr XSetWindowAttributes |
|
type Pixel = Word32 |
|
type Position = Int32 |
|
type Dimension = Word32 |
|
type Angle = Int |
|
type ScreenNumber = Word32 |
|
type Byte = Word8 |
|
type Buffer = Int |
|
type ShortPosition = Int16 |
|
type ShortDimension = Word16 |
|
type ShortAngle = Int16 |
|
type Short = Int16 |
|
peekPositionField :: Ptr a -> Int -> IO Position |
|
peekDimensionField :: Ptr a -> Int -> IO Dimension |
|
peekAngleField :: Ptr a -> Int -> IO Angle |
|
pokePositionField :: Ptr a -> Int -> Position -> IO () |
|
pokeDimensionField :: Ptr a -> Int -> Dimension -> IO () |
|
pokeAngleField :: Ptr a -> Int -> Angle -> IO () |
|
data Storable' a |
Constructors | Storable' | | size :: Int | | peek' :: (Ptr a -> IO a) | | poke' :: (Ptr a -> a -> IO ()) | |
|
|
|
|
alloca' :: Storable' a -> (Ptr a -> IO b) -> IO b |
|
withStorable' :: Storable' a -> a -> (Ptr a -> IO b) -> IO b |
|
peekElemOff' :: Storable' a -> Ptr a -> Int -> IO a |
|
pokeElemOff' :: Storable' a -> Ptr a -> Int -> a -> IO () |
|
peekArray' :: Storable' a -> Int -> Ptr a -> IO [a] |
|
pokeArray' :: Storable' a -> Ptr a -> [a] -> IO () |
|
withArray' :: Storable' a -> [a] -> (Ptr a -> Int -> IO b) -> IO b |
|
type Point = (Position, Position) |
counterpart of an X11 XPoint structure
|
|
s_Point :: Storable' Point |
|
peekPoint :: Ptr Point -> IO Point |
|
pokePoint :: Ptr Point -> Point -> IO () |
|
peekPointArray :: Int -> Ptr Point -> IO [Point] |
|
withPointArray :: [Point] -> (Ptr Point -> Int -> IO b) -> IO b |
|
type Rectangle = (Position, Position, Dimension, Dimension) |
counterpart of an X11 XRectangle structure
|
|
s_Rectangle :: Storable' Rectangle |
|
peekRectangle :: Ptr Rectangle -> IO Rectangle |
|
pokeRectangle :: Ptr Rectangle -> Rectangle -> IO () |
|
allocaRectangle :: (Ptr Rectangle -> IO a) -> IO a |
|
withRectangle :: Rectangle -> (Ptr Rectangle -> IO a) -> IO a |
|
peekRectangleArray :: Int -> Ptr Rectangle -> IO [Rectangle] |
|
withRectangleArray :: [Rectangle] -> (Ptr Rectangle -> Int -> IO b) -> IO b |
|
type Arc = (Position, Position, Dimension, Dimension, Angle, Angle) |
counterpart of an X11 XArc structure
|
|
s_Arc :: Storable' Arc |
|
peekArc :: Ptr Arc -> IO Arc |
|
pokeArc :: Ptr Arc -> Arc -> IO () |
|
peekArcArray :: Int -> Ptr Arc -> IO [Arc] |
|
withArcArray :: [Arc] -> (Ptr Arc -> Int -> IO b) -> IO b |
|
type Segment = (Position, Position, Position, Position) |
counterpart of an X11 XSegment structure
|
|
s_Segment :: Storable' Segment |
|
peekSegment :: Ptr Segment -> IO Segment |
|
pokeSegment :: Ptr Segment -> Segment -> IO () |
|
peekSegmentArray :: Int -> Ptr Segment -> IO [Segment] |
|
withSegmentArray :: [Segment] -> (Ptr Segment -> Int -> IO b) -> IO b |
|
type Color = (Pixel, Word16, Word16, Word16, Word8) |
counterpart of an X11 XColor structure
|
|
s_Color :: Storable' Color |
|
peekColor :: Ptr Color -> IO Color |
|
pokeColor :: Ptr Color -> Color -> IO () |
|
allocaColor :: (Ptr Color -> IO a) -> IO a |
|
withColor :: Color -> (Ptr Color -> IO a) -> IO a |
|
peekColorArray :: Int -> Ptr Color -> IO [Color] |
|
withColorArray :: [Color] -> (Ptr Color -> Int -> IO b) -> IO b |
|
type ListPoint = [Point] |
|
type ListRectangle = [Rectangle] |
|
type ListArc = [Arc] |
|
type ListSegment = [Segment] |
|
type ListColor = [Color] |
|
Produced by Haddock version 0.7 |