| Safe Haskell | None | 
|---|
Graphics.Rendering.FTGL
Description
- Author: Jefferson Heard (jefferson.r.heard at gmail.com)
- Copyright 2008 Renaissance Computing Institute http://www.renci.org
- License: GNU LGPL
- Compatibility GHC (I could change the data declarations to not be empty and that would make it more generally compatible, I believe)
- Description:
Use FreeType 2 Fonts in OpenGL. Requires the FTGL library and FreeType libraries. available at http://ftgl.wiki.sourceforge.net/ . The most important functions for everyday use are renderFont and the create*Font family of functions. To render a simple string inside OpenGL, assuming you have OpenGL initialized and a current pen color, all you need is:
do font <- createTextureFont "Font.ttf" setFontFaceSize font 24 72 renderFont font "Hello world!"
Fonts are rendered so that a single point is an OpenGL unit, and a point is 1:72 of an inch.
- fcreateBitmapFont :: CString -> IO Font
- createBitmapFont :: ByteString -> IO Font
- fcreateBufferFont :: CString -> IO Font
- createBufferFont :: ByteString -> IO Font
- fcreateOutlineFont :: CString -> IO Font
- createOutlineFont :: ByteString -> IO Font
- fcreatePixmapFont :: CString -> IO Font
- createPixmapFont :: ByteString -> IO Font
- fcreatePolygonFont :: CString -> IO Font
- createPolygonFont :: ByteString -> IO Font
- fcreateTextureFont :: CString -> IO Font
- createTextureFont :: ByteString -> IO Font
- fcreateExtrudeFont :: CString -> IO Font
- createExtrudeFont :: ByteString -> IO Font
- createSimpleLayout :: IO Layout
- setLayoutFont :: Layout -> Font -> IO ()
- getLayoutFont :: Layout -> IO Font
- layoutFont :: MonadIO m => Layout -> StateVar m Font
- setLayoutLineLength :: Layout -> CFloat -> IO ()
- fgetLayoutLineLength :: Layout -> IO CFloat
- layoutLineLength :: MonadIO m => Layout -> StateVar m CFloat
- fsetLayoutAlignment :: Layout -> CInt -> IO ()
- fgetLayoutAlignment :: Layout -> IO CInt
- layoutAlignment :: MonadIO m => Layout -> StateVar m TextAlignment
- fsetLayoutLineSpacing :: Layout -> CFloat -> IO ()
- layoutLineSpacing :: MonadIO m => Layout -> SettableStateVar m Float
- destroyFont :: Font -> IO ()
- fattachFile :: Font -> CString -> IO ()
- attachFile :: Font -> ByteString -> IO ()
- attachData :: Font -> Ptr () -> IO ()
- fsetFontCharMap :: Font -> CInt -> IO ()
- charMap :: MonadIO m => Font -> SettableStateVar m CharMap
- fgetFontCharMapCount :: Font -> IO CInt
- getFontCharMapCount :: Font -> Int
- fgetFontCharMapList :: Font -> IO (Ptr CInt)
- getFontCharMapList :: Font -> Ptr CInt
- fsetFontFaceSize :: Font -> CInt -> CInt -> IO CInt
- setFontFaceSize :: Font -> Int -> Int -> IO CInt
- fgetFontFaceSize :: Font -> IO CInt
- fontFaceSize :: MonadIO m => Font -> GettableStateVar m Int
- fsetFontDepth :: Font -> CFloat -> IO ()
- fontDepth :: MonadIO m => Font -> SettableStateVar m Float
- fsetFontOutset :: Font -> CFloat -> CFloat -> IO ()
- setFontOutset :: Font -> Float -> Float -> IO ()
- fgetFontBBox :: Font -> CString -> Int -> Ptr CFloat -> IO ()
- getFontBBox :: Font -> ByteString -> IO [Float]
- fgetFontAscender :: Font -> CFloat
- getFontAscender :: Font -> Float
- fgetFontDescender :: Font -> CFloat
- getFontDescender :: Font -> Float
- fgetFontLineHeight :: Font -> CFloat
- getFontLineHeight :: Font -> Float
- fgetFontAdvance :: Font -> CString -> IO CFloat
- getFontAdvance :: Font -> ByteString -> IO Float
- frenderFont :: Font -> CString -> CInt -> IO ()
- renderFont :: Font -> RenderMode -> ByteString -> IO ()
- fgetFontError :: Font -> IO CInt
- fontError :: MonadIO m => Font -> GettableStateVar m Int
- destroyLayout :: Layout -> IO ()
- frenderLayout :: Layout -> CString -> IO ()
- renderLayout :: Layout -> ByteString -> IO ()
- fgetLayoutError :: Layout -> IO CInt
- layoutError :: MonadIO m => Layout -> GettableStateVar m CInt
- data RenderMode
- data  TextAlignment - = AlignLeft
- | AlignCenter
- | AlignRight
- | Justify
 
- data Glyph_Opaque
- data Font_Opaque
- data Layout_Opaque
- type Glyph = Ptr Glyph_Opaque
- type Font = Ptr Font_Opaque
- type Layout = Ptr Layout_Opaque
- data CharMap
- encodeTag :: Char -> Char -> Char -> Char -> CInt
- marshalCharMap :: CharMap -> CInt
Documentation
fcreateBitmapFont :: CString -> IO FontSource
createBitmapFont :: ByteString -> IO FontSource
Create a bitmapped version of a TrueType font. Bitmapped versions will not | respond to matrix transformations, but rather must be transformed using the | raster positioning functions in OpenGL
fcreateBufferFont :: CString -> IO FontSource
createBufferFont :: ByteString -> IO FontSource
Create a buffered version of a TrueType font. This stores the entirety of | a string in a texture, buffering it before rendering. Very fast if you | will be repeatedly rendering the same strings over and over.
createOutlineFont :: ByteString -> IO FontSource
Create an outline version of a TrueType font. This uses actual geometry | and will scale independently without loss of quality. Faster than polygons | but slower than texture or buffer fonts.
fcreatePixmapFont :: CString -> IO FontSource
createPixmapFont :: ByteString -> IO FontSource
Create a pixmap version of a TrueType font. Higher quality than the bitmap | font without losing any performance. Use this if you don't mind using | set and get RasterPosition.
createPolygonFont :: ByteString -> IO FontSource
Create polygonal display list fonts. These scale independently without | losing quality, unlike texture or buffer fonts, but can be impractical | for large amounts of text because of the high number of polygons needed. | Additionally, they do not, unlike the textured fonts, create artifacts | within the square formed at the edge of each character.
createTextureFont :: ByteString -> IO FontSource
Create textured display list fonts. These can scale somewhat well, | but lose quality quickly. They are much faster than polygonal fonts, | though, so are suitable for large quantities of text. Especially suited | well to text that changes with most frames, because it doesn't incur the | (normally helpful) overhead of buffering.
createExtrudeFont :: ByteString -> IO FontSource
Create a 3D extruded font. This is the only way of creating 3D fonts | within FTGL. Could be fun to use a geometry shader to get different | effects by warping the otherwise square nature of the font. Polygonal. | Scales without losing quality. Slower than all other fonts.
createSimpleLayout :: IO LayoutSource
Create a simple layout
setLayoutFont :: Layout -> Font -> IO ()Source
Set the layout's font.
getLayoutFont :: Layout -> IO FontSource
Get the embedded font from the Layout
setLayoutLineLength :: Layout -> CFloat -> IO ()Source
Set the line length, I believe in OpenGL units, although I'm not sure.
fsetLayoutAlignment :: Layout -> CInt -> IO ()Source
layoutAlignment :: MonadIO m => Layout -> StateVar m TextAlignmentSource
fsetLayoutLineSpacing :: Layout -> CFloat -> IO ()Source
layoutLineSpacing :: MonadIO m => Layout -> SettableStateVar m FloatSource
destroyFont :: Font -> IO ()Source
Destroy a font
fattachFile :: Font -> CString -> IO ()Source
attachFile :: Font -> ByteString -> IO ()Source
Attach a metadata file to a font.
attachData :: Font -> Ptr () -> IO ()Source
Attach some external data (often kerning) to the font
fsetFontCharMap :: Font -> CInt -> IO ()Source
Set the font's character map
fgetFontCharMapCount :: Font -> IO CIntSource
getFontCharMapCount :: Font -> IntSource
Get the number of characters loaded into the current charmap for the font.
getFontCharMapList :: Font -> Ptr CIntSource
Get the different character mappings available in this font.
fgetFontFaceSize :: Font -> IO CIntSource
fontFaceSize :: MonadIO m => Font -> GettableStateVar m IntSource
Get the current font face size in points.
fsetFontDepth :: Font -> CFloat -> IO ()Source
getFontBBox :: Font -> ByteString -> IO [Float]Source
Get the text extents of a string as a list of (llx,lly,lly,urx,ury,urz)
fgetFontAscender :: Font -> CFloatSource
getFontAscender :: Font -> FloatSource
Get the global ascender height for the face.
getFontDescender :: Font -> FloatSource
Gets the global descender height for the face.
getFontLineHeight :: Font -> FloatSource
Gets the global line spacing for the face.
getFontAdvance :: Font -> ByteString -> IO FloatSource
Get the horizontal span of a string of text using the current font. Input as the xcoord | in any translate operation
renderFont :: Font -> RenderMode -> ByteString -> IO ()Source
Render a string of text in the current font.
fgetFontError :: Font -> IO CIntSource
fontError :: MonadIO m => Font -> GettableStateVar m IntSource
Get any errors associated with loading a font. FIXME return should be a type, not an Int.
destroyLayout :: Layout -> IO ()Source
frenderLayout :: Layout -> CString -> IO ()Source
renderLayout :: Layout -> ByteString -> IO ()Source
Render a string of text within a layout.
fgetLayoutError :: Layout -> IO CIntSource
layoutError :: MonadIO m => Layout -> GettableStateVar m CIntSource
Get any errors associated with a layout.
data RenderMode Source
Whether or not in polygonal or extrusion mode, the font will render equally front and back
Instances
data TextAlignment Source
In a Layout directed render, the layout mode of the text
Constructors
| AlignLeft | |
| AlignCenter | |
| AlignRight | |
| Justify | 
Instances
data Glyph_Opaque Source
An opaque type encapsulating a glyph in C. Currently the glyph functions are unimplemented in Haskell.
data Font_Opaque Source
An opaque type encapsulating a font in C.
data Layout_Opaque Source
An opaque type encapsulating a layout in C
type Glyph = Ptr Glyph_OpaqueSource
type Font = Ptr Font_OpaqueSource
type Layout = Ptr Layout_OpaqueSource
marshalCharMap :: CharMap -> CIntSource