xosd-0.2.1: A binding to the X on-screen display

PortabilityCPP, FFI
StabilityStable
MaintainerDon Stewart <dons00@gmail.com>
Safe HaskellNone

Graphics.XOSD.Base

Contents

Description

Tested with: GHC 6.10, GHC 7.6

Bindings to xosd, the X on-screen display library xosd is a library for displaying an on-screen display (like the one on many TVs) on your X display.

An example using the lowest level C layer:

 do x <- create 1
    setFont x "-adobe-helvetica-bold-r-*-*-34-*-*-*-*-*-*-*"
    setColor x "LimeGreen"
    display x 0 (String "Screen 1")

runXOSD [Timeout 10, VAlign VAlignMiddle, HAlign HAlignCenter, Font -adobe-helvetica-bold-r-*-*-34-*-*-*-*-*-*-*, Color LimeGreen, Display (String TEST)] (x -> sequence_ [ display x 0 (String (show i)) >> Control.Concurrent.threadDelay (10^4) | i <- [1..] ])

Synopsis

The abstract XOSD type

type XOSD = Ptr XOSD_Source

An abstract X on-screen display object

An xosd window can be used to display textual or numerical data on a X11 display in a unmanaged, shaped window that appears to be transparent. It provides a similar effect to the on-screen display of many televisions and video recorders

Formatting types

data VAlign Source

Valid screen positions (vertical alignment)

data HAlign Source

Valid screen positions (vertical alignment)

data Format Source

The type of possible display formats

Constructors

Percent !Int 
Slider !Int 
String String 

Introduction and elimination

create :: Int -> IO XOSDSource

Create a new xosd window. The argument is the maximum number of lines of text that the window can display. Throw an exception on failure.

destroy :: XOSD -> IO ()Source

xosd_uninit destroys an existing xosd window, freeing the memory. This is an unsafe function: as destroying an xosd object twice will likely cause bad things to happen, so don't do that.

Error handling

xosdEitherIf :: (a -> Bool) -> IO a -> IO (Either String a)Source

Throw an error (encapsulated in Either) with the current String in xosd_error

xosdErrorIf :: (a -> Bool) -> IO a -> IO aSource

Throw an error with the current String in xosd_error if predicate is True when applied to result of action.

xosdError :: IO aSource

Throw an error with the current String in xosd_error unconditionally

Setting attributes in the xosd object

setBarLength :: XOSD -> Int -> IO ()Source

Set length of percentage and slider bar

setShadowOffset :: XOSD -> Int -> IO ()Source

Change the offset of the text shadow

setShadowColor :: XOSD -> String -> IO ()Source

Change the colour of the shadow

setOutlineOffset :: XOSD -> Int -> IO ()Source

Change the offset of the text outline- The outline is drawn over the shadow.

setOutlineColor :: XOSD -> String -> IO ()Source

Change the colour of the outline

setHorizontalOffset :: XOSD -> Int -> IO ()Source

Change the number of pixels the display is offset from the position

setVerticalOffset :: XOSD -> Int -> IO ()Source

Change the number of pixels the display is offset from the position

setTimeout :: XOSD -> Int -> IO ()Source

Change the time before display is hidden.

setColor :: XOSD -> String -> IO ()Source

Change the colour of the display

setFont :: XOSD -> String -> IO ()Source

Change the text-display font

display :: XOSD -> Int -> Format -> IO ()Source

Display some content.

setHidden :: XOSD -> IO ()Source

Hide the display

setVisible :: XOSD -> IO ()Source

Show the display after being hidden

scroll :: XOSD -> Int -> IO ()Source

Scroll the display

Testing state of the xosd object

getNumberOfLines :: XOSD -> IO IntSource

Get the maximum number of lines allowed

Control structures

wait :: XOSD -> IO ()Source

Wait until nothing is displayed. Blocks the process until no longer visible.

Helpers

toXOSDVAlign :: VAlign -> XOSD_VAlignSource

Translate abstract to concrete formatting types

toXOSDHAlign :: HAlign -> XOSD_HAlignSource

Translate abstract to concrete formatting types

toXOSDFormat :: Format -> XOSD_FormatSource

Translate abstract to concrete formatting types

Raw C API

xosd_display_string :: XOSD -> CInt -> XOSD_Format -> CString -> IO CIntSource

xosd_display_percent :: XOSD -> CInt -> XOSD_Format -> CInt -> IO CIntSource

xosd_display_slider :: XOSD -> CInt -> XOSD_Format -> CInt -> IO CIntSource