Safe Haskell | None |
---|---|
Language | Haskell98 |
FreeType.Core.Glyph
Contents
Description
Please refer to the Core API > Glyph Management chapter of the reference.
Internal: FreeType.Core.Glyph.Internal.
Synopsis
- type FT_Glyph = Ptr FT_GlyphRec
- data FT_GlyphRec = FT_GlyphRec {
- grLibrary :: FT_Library
- grClazz :: Ptr FT_Glyph_Class
- grFormat :: FT_Glyph_Format
- grAdvance :: FT_Vector
- type FT_BitmapGlyph = Ptr FT_BitmapGlyphRec
- data FT_BitmapGlyphRec = FT_BitmapGlyphRec {}
- data FT_OutlineGlyph
- data FT_OutlineGlyphRec = FT_OutlineGlyphRec {}
- ft_New_Glyph :: FT_Library -> FT_Glyph_Format -> IO FT_Glyph
- ft_With_Glyph :: FT_Library -> FT_Glyph_Format -> (FT_Glyph -> IO a) -> IO a
- ft_Get_Glyph :: FT_GlyphSlot -> IO FT_Glyph
- ft_Glyph_Copy :: FT_Glyph -> Ptr FT_Glyph -> IO ()
- ft_Glyph_Transform :: FT_Glyph -> FT_Matrix -> FT_Vector -> IO ()
- pattern FT_GLYPH_BBOX_UNSCALED :: (Eq a, Num a) => a
- pattern FT_GLYPH_BBOX_SUBPIXELS :: (Eq a, Num a) => a
- pattern FT_GLYPH_BBOX_GRIDFIT :: (Eq a, Num a) => a
- pattern FT_GLYPH_BBOX_TRUNCATE :: (Eq a, Num a) => a
- pattern FT_GLYPH_BBOX_PIXELS :: (Eq a, Num a) => a
- ft_Glyph_Get_CBox :: FT_Glyph -> FT_UInt -> IO FT_BBox
- ft_Glyph_To_Bitmap :: Ptr FT_Glyph -> FT_Render_Mode -> Ptr FT_Vector -> Bool -> IO ()
- ft_Done_Glyph :: FT_Glyph -> IO ()
FT_Glyph
type FT_Glyph = Ptr FT_GlyphRec Source #
FT_GlyphRec
data FT_GlyphRec Source #
Constructors
FT_GlyphRec | |
Fields
|
Instances
Storable FT_GlyphRec Source # | |
Defined in FreeType.Core.Glyph.Types Methods sizeOf :: FT_GlyphRec -> Int # alignment :: FT_GlyphRec -> Int # peekElemOff :: Ptr FT_GlyphRec -> Int -> IO FT_GlyphRec # pokeElemOff :: Ptr FT_GlyphRec -> Int -> FT_GlyphRec -> IO () # peekByteOff :: Ptr b -> Int -> IO FT_GlyphRec # pokeByteOff :: Ptr b -> Int -> FT_GlyphRec -> IO () # peek :: Ptr FT_GlyphRec -> IO FT_GlyphRec # poke :: Ptr FT_GlyphRec -> FT_GlyphRec -> IO () # |
FT_BitmapGlyph
type FT_BitmapGlyph = Ptr FT_BitmapGlyphRec Source #
FT_BitmapGlyphRec
data FT_BitmapGlyphRec Source #
Constructors
FT_BitmapGlyphRec | |
Instances
Storable FT_BitmapGlyphRec Source # | |
Defined in FreeType.Core.Glyph.Types Methods sizeOf :: FT_BitmapGlyphRec -> Int # alignment :: FT_BitmapGlyphRec -> Int # peekElemOff :: Ptr FT_BitmapGlyphRec -> Int -> IO FT_BitmapGlyphRec # pokeElemOff :: Ptr FT_BitmapGlyphRec -> Int -> FT_BitmapGlyphRec -> IO () # peekByteOff :: Ptr b -> Int -> IO FT_BitmapGlyphRec # pokeByteOff :: Ptr b -> Int -> FT_BitmapGlyphRec -> IO () # peek :: Ptr FT_BitmapGlyphRec -> IO FT_BitmapGlyphRec # poke :: Ptr FT_BitmapGlyphRec -> FT_BitmapGlyphRec -> IO () # |
FT_OutlineGlyph
data FT_OutlineGlyph Source #
FT_OutlineGlyphRec
data FT_OutlineGlyphRec Source #
Constructors
FT_OutlineGlyphRec | |
Fields |
Instances
Storable FT_OutlineGlyphRec Source # | |
Defined in FreeType.Core.Glyph.Types Methods sizeOf :: FT_OutlineGlyphRec -> Int # alignment :: FT_OutlineGlyphRec -> Int # peekElemOff :: Ptr FT_OutlineGlyphRec -> Int -> IO FT_OutlineGlyphRec # pokeElemOff :: Ptr FT_OutlineGlyphRec -> Int -> FT_OutlineGlyphRec -> IO () # peekByteOff :: Ptr b -> Int -> IO FT_OutlineGlyphRec # pokeByteOff :: Ptr b -> Int -> FT_OutlineGlyphRec -> IO () # peek :: Ptr FT_OutlineGlyphRec -> IO FT_OutlineGlyphRec # poke :: Ptr FT_OutlineGlyphRec -> FT_OutlineGlyphRec -> IO () # |
FT_New_Glyph
Arguments
:: FT_Library | library |
-> FT_Glyph_Format | format |
-> IO FT_Glyph | glyph |
Arguments
:: FT_Library | library |
-> FT_Glyph_Format | format |
-> (FT_Glyph -> IO a) | |
-> IO a |
bracket
over ft_New_Glyph
and ft_With_Glyph
.
The provided FT_Glyph
should not be used after this function terminates.
FT_Get_Glyph
Arguments
:: FT_GlyphSlot | slot |
-> IO FT_Glyph | glyph |
FT_Glyph_Copy
FT_Glyph_Transform
FT_Glyph_BBox_Mode
pattern FT_GLYPH_BBOX_UNSCALED :: (Eq a, Num a) => a Source #
pattern FT_GLYPH_BBOX_SUBPIXELS :: (Eq a, Num a) => a Source #
pattern FT_GLYPH_BBOX_GRIDFIT :: (Eq a, Num a) => a Source #
pattern FT_GLYPH_BBOX_TRUNCATE :: (Eq a, Num a) => a Source #
pattern FT_GLYPH_BBOX_PIXELS :: (Eq a, Num a) => a Source #