module Graphics.Rendering.Pango.Types (
module System.Glib.GObject,
PangoContext(PangoContext), PangoContextClass,
toPangoContext,
mkPangoContext, unPangoContext,
castToPangoContext, gTypePangoContext,
PangoLayoutRaw(PangoLayoutRaw), PangoLayoutRawClass,
toPangoLayoutRaw,
mkPangoLayoutRaw, unPangoLayoutRaw,
castToPangoLayoutRaw, gTypePangoLayoutRaw,
Font(Font), FontClass,
toFont,
mkFont, unFont,
castToFont, gTypeFont,
FontFamily(FontFamily), FontFamilyClass,
toFontFamily,
mkFontFamily, unFontFamily,
castToFontFamily, gTypeFontFamily,
FontFace(FontFace), FontFaceClass,
toFontFace,
mkFontFace, unFontFace,
castToFontFace, gTypeFontFace,
FontMap(FontMap), FontMapClass,
toFontMap,
mkFontMap, unFontMap,
castToFontMap, gTypeFontMap,
FontSet(FontSet), FontSetClass,
toFontSet,
mkFontSet, unFontSet,
castToFontSet, gTypeFontSet
) where
import Foreign.ForeignPtr (ForeignPtr, castForeignPtr, unsafeForeignPtrToPtr)
import Foreign.C.Types (CULong(..), CUInt(..))
import System.Glib.GType (GType, typeInstanceIsA)
import System.Glib.GObject
castTo :: (GObjectClass obj, GObjectClass obj') => GType -> String
-> (obj -> obj')
castTo gtype objTypeName obj =
case toGObject obj of
gobj@(GObject objFPtr)
| typeInstanceIsA ((unsafeForeignPtrToPtr.castForeignPtr) objFPtr) gtype
-> unsafeCastGObject gobj
| otherwise -> error $ "Cannot cast object to " ++ objTypeName
newtype PangoContext = PangoContext (ForeignPtr (PangoContext)) deriving (Eq,Ord)
mkPangoContext = (PangoContext, objectUnref)
unPangoContext (PangoContext o) = o
class GObjectClass o => PangoContextClass o
toPangoContext :: PangoContextClass o => o -> PangoContext
toPangoContext = unsafeCastGObject . toGObject
instance PangoContextClass PangoContext
instance GObjectClass PangoContext where
toGObject = GObject . castForeignPtr . unPangoContext
unsafeCastGObject = PangoContext . castForeignPtr . unGObject
castToPangoContext :: GObjectClass obj => obj -> PangoContext
castToPangoContext = castTo gTypePangoContext "PangoContext"
gTypePangoContext :: GType
gTypePangoContext =
pango_context_get_type
newtype PangoLayoutRaw = PangoLayoutRaw (ForeignPtr (PangoLayoutRaw)) deriving (Eq,Ord)
mkPangoLayoutRaw = (PangoLayoutRaw, objectUnref)
unPangoLayoutRaw (PangoLayoutRaw o) = o
class GObjectClass o => PangoLayoutRawClass o
toPangoLayoutRaw :: PangoLayoutRawClass o => o -> PangoLayoutRaw
toPangoLayoutRaw = unsafeCastGObject . toGObject
instance PangoLayoutRawClass PangoLayoutRaw
instance GObjectClass PangoLayoutRaw where
toGObject = GObject . castForeignPtr . unPangoLayoutRaw
unsafeCastGObject = PangoLayoutRaw . castForeignPtr . unGObject
castToPangoLayoutRaw :: GObjectClass obj => obj -> PangoLayoutRaw
castToPangoLayoutRaw = castTo gTypePangoLayoutRaw "PangoLayoutRaw"
gTypePangoLayoutRaw :: GType
gTypePangoLayoutRaw =
pango_layout_get_type
newtype Font = Font (ForeignPtr (Font)) deriving (Eq,Ord)
mkFont = (Font, objectUnref)
unFont (Font o) = o
class GObjectClass o => FontClass o
toFont :: FontClass o => o -> Font
toFont = unsafeCastGObject . toGObject
instance FontClass Font
instance GObjectClass Font where
toGObject = GObject . castForeignPtr . unFont
unsafeCastGObject = Font . castForeignPtr . unGObject
castToFont :: GObjectClass obj => obj -> Font
castToFont = castTo gTypeFont "Font"
gTypeFont :: GType
gTypeFont =
pango_font_get_type
newtype FontFamily = FontFamily (ForeignPtr (FontFamily)) deriving (Eq,Ord)
mkFontFamily = (FontFamily, objectUnref)
unFontFamily (FontFamily o) = o
class GObjectClass o => FontFamilyClass o
toFontFamily :: FontFamilyClass o => o -> FontFamily
toFontFamily = unsafeCastGObject . toGObject
instance FontFamilyClass FontFamily
instance GObjectClass FontFamily where
toGObject = GObject . castForeignPtr . unFontFamily
unsafeCastGObject = FontFamily . castForeignPtr . unGObject
castToFontFamily :: GObjectClass obj => obj -> FontFamily
castToFontFamily = castTo gTypeFontFamily "FontFamily"
gTypeFontFamily :: GType
gTypeFontFamily =
pango_font_family_get_type
newtype FontFace = FontFace (ForeignPtr (FontFace)) deriving (Eq,Ord)
mkFontFace = (FontFace, objectUnref)
unFontFace (FontFace o) = o
class GObjectClass o => FontFaceClass o
toFontFace :: FontFaceClass o => o -> FontFace
toFontFace = unsafeCastGObject . toGObject
instance FontFaceClass FontFace
instance GObjectClass FontFace where
toGObject = GObject . castForeignPtr . unFontFace
unsafeCastGObject = FontFace . castForeignPtr . unGObject
castToFontFace :: GObjectClass obj => obj -> FontFace
castToFontFace = castTo gTypeFontFace "FontFace"
gTypeFontFace :: GType
gTypeFontFace =
pango_font_face_get_type
newtype FontMap = FontMap (ForeignPtr (FontMap)) deriving (Eq,Ord)
mkFontMap = (FontMap, objectUnref)
unFontMap (FontMap o) = o
class GObjectClass o => FontMapClass o
toFontMap :: FontMapClass o => o -> FontMap
toFontMap = unsafeCastGObject . toGObject
instance FontMapClass FontMap
instance GObjectClass FontMap where
toGObject = GObject . castForeignPtr . unFontMap
unsafeCastGObject = FontMap . castForeignPtr . unGObject
castToFontMap :: GObjectClass obj => obj -> FontMap
castToFontMap = castTo gTypeFontMap "FontMap"
gTypeFontMap :: GType
gTypeFontMap =
pango_font_face_get_type
newtype FontSet = FontSet (ForeignPtr (FontSet)) deriving (Eq,Ord)
mkFontSet = (FontSet, objectUnref)
unFontSet (FontSet o) = o
class GObjectClass o => FontSetClass o
toFontSet :: FontSetClass o => o -> FontSet
toFontSet = unsafeCastGObject . toGObject
instance FontSetClass FontSet
instance GObjectClass FontSet where
toGObject = GObject . castForeignPtr . unFontSet
unsafeCastGObject = FontSet . castForeignPtr . unGObject
castToFontSet :: GObjectClass obj => obj -> FontSet
castToFontSet = castTo gTypeFontSet "FontSet"
gTypeFontSet :: GType
gTypeFontSet =
pango_fontset_get_type
foreign import ccall unsafe "pango_context_get_type"
pango_context_get_type :: CUInt
foreign import ccall unsafe "pango_layout_get_type"
pango_layout_get_type :: CUInt
foreign import ccall unsafe "pango_font_get_type"
pango_font_get_type :: CUInt
foreign import ccall unsafe "pango_font_family_get_type"
pango_font_family_get_type :: CUInt
foreign import ccall unsafe "pango_font_face_get_type"
pango_font_face_get_type :: CUInt
foreign import ccall unsafe "pango_fontset_get_type"
pango_fontset_get_type :: CUInt