Safe Haskell | None |
---|---|
Language | Haskell98 |
- 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!" Front
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 :: String -> IO Font
- fcreateBufferFont :: CString -> IO Font
- createBufferFont :: String -> IO Font
- fcreateOutlineFont :: CString -> IO Font
- createOutlineFont :: String -> IO Font
- fcreatePixmapFont :: CString -> IO Font
- createPixmapFont :: String -> IO Font
- fcreatePolygonFont :: CString -> IO Font
- createPolygonFont :: String -> IO Font
- fcreateTextureFont :: CString -> IO Font
- createTextureFont :: String -> IO Font
- fcreateExtrudeFont :: CString -> IO Font
- createExtrudeFont :: String -> IO Font
- createSimpleLayout :: IO Layout
- setLayoutFont :: Layout -> Font -> IO ()
- fgetLayoutFont :: Layout -> IO Font
- getLayoutFont :: Layout -> IO Font
- setLayoutLineLength :: Layout -> CFloat -> IO ()
- fgetLayoutLineLength :: Layout -> IO CFloat
- getLayoutLineLength :: Layout -> IO Float
- fsetLayoutAlignment :: Layout -> CInt -> IO ()
- setLayoutAlignment :: Layout -> TextAlignment -> IO ()
- fgetLayoutAlignment :: Layout -> IO CInt
- getLayoutAlignment :: Layout -> IO TextAlignment
- fsetLayoutLineSpacing :: Layout -> CFloat -> IO ()
- setLayoutLineSpacing :: Layout -> Float -> IO ()
- destroyFont :: Font -> IO ()
- fattachFile :: Font -> CString -> IO ()
- attachFile :: Font -> String -> IO ()
- attachData :: Font -> Ptr () -> IO ()
- fsetFontCharMap :: Font -> CInt -> IO ()
- setCharMap :: Font -> CharMap -> IO ()
- 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
- getFontFaceSize :: Font -> IO Int
- fsetFontDepth :: Font -> CFloat -> IO ()
- setFontDepth :: Font -> Float -> IO ()
- fsetFontOutset :: Font -> CFloat -> CFloat -> IO ()
- setFontOutset :: Font -> Float -> Float -> IO ()
- fgetFontBBox :: Font -> CString -> Int -> Ptr CFloat -> IO ()
- getFontBBox :: Font -> String -> 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 -> String -> IO Float
- frenderFont :: Font -> CString -> CInt -> IO ()
- renderFont :: Font -> String -> RenderMode -> IO ()
- fgetFontError :: Font -> IO CInt
- getFontError :: Font -> IO Int
- destroyLayout :: Layout -> IO ()
- frenderLayout :: Layout -> CString -> IO ()
- renderLayout :: Layout -> String -> IO ()
- fgetLayoutError :: Layout -> IO CInt
- getLayoutError :: Layout -> IO CInt
- data RenderMode
- data TextAlignment
- marshalRenderMode :: RenderMode -> CInt
- marshalTextAlignment :: TextAlignment -> CInt
- readTextAlignment :: CInt -> TextAlignment
- data GlyphOpaque
- data FontOpaque
- data LayoutOpaque
- type Glyph = Ptr GlyphOpaque
- type Font = Ptr FontOpaque
- type Layout = Ptr LayoutOpaque
- data CharMap
- encodeTag :: Char -> Char -> Char -> Char -> CInt
- marshalCharMap :: CharMap -> CInt
Documentation
fcreateBitmapFont :: CString -> IO Font Source
createBitmapFont :: String -> IO Font Source
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 Font Source
createBufferFont :: String -> IO Font Source
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.
fcreateOutlineFont :: CString -> IO Font Source
createOutlineFont :: String -> IO Font Source
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 Font Source
createPixmapFont :: String -> IO Font Source
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.
fcreatePolygonFont :: CString -> IO Font Source
createPolygonFont :: String -> IO Font Source
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.
fcreateTextureFont :: CString -> IO Font Source
createTextureFont :: String -> IO Font Source
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.
fcreateExtrudeFont :: CString -> IO Font Source
createExtrudeFont :: String -> IO Font Source
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 Layout Source
Create a simple layout
setLayoutFont :: Layout -> Font -> IO () Source
Set the layout's font.
fgetLayoutFont :: Layout -> IO Font Source
getLayoutFont :: Layout -> IO Font Source
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.
fgetLayoutLineLength :: Layout -> IO CFloat Source
getLayoutLineLength :: Layout -> IO Float Source
Get the line length in points (1:72in) of lines in the layout
fsetLayoutAlignment :: Layout -> CInt -> IO () Source
setLayoutAlignment :: Layout -> TextAlignment -> IO () Source
Set the layout alignment
fgetLayoutAlignment :: Layout -> IO CInt Source
getLayoutAlignment :: Layout -> IO TextAlignment Source
Get the alignment of text in this layout.
fsetLayoutLineSpacing :: Layout -> CFloat -> IO () Source
setLayoutLineSpacing :: Layout -> Float -> IO () Source
Set layout line spacing in OpenGL units.
destroyFont :: Font -> IO () Source
Destroy a font
fattachFile :: Font -> CString -> IO () Source
attachFile :: Font -> String -> 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
setCharMap :: Font -> CharMap -> IO () Source
fgetFontCharMapCount :: Font -> IO CInt Source
getFontCharMapCount :: Font -> Int Source
Get the number of characters loaded into the current charmap for the font.
getFontCharMapList :: Font -> Ptr CInt Source
Get the different character mappings available in this font.
fgetFontFaceSize :: Font -> IO CInt Source
getFontFaceSize :: Font -> IO Int Source
Get the current font face size in points.
fsetFontDepth :: Font -> CFloat -> IO () Source
setFontDepth :: Font -> Float -> IO () Source
getFontBBox :: Font -> String -> IO [Float] Source
Get the text extents of a string as a list of (llx,lly,lly,urx,ury,urz)
fgetFontAscender :: Font -> CFloat Source
getFontAscender :: Font -> Float Source
Get the global ascender height for the face.
fgetFontDescender :: Font -> CFloat Source
getFontDescender :: Font -> Float Source
Gets the global descender height for the face.
fgetFontLineHeight :: Font -> CFloat Source
getFontLineHeight :: Font -> Float Source
Gets the global line spacing for the face.
getFontAdvance :: Font -> String -> IO Float Source
Get the horizontal span of a string of text using the current font. Input as the xcoord | in any translate operation
renderFont :: Font -> String -> RenderMode -> IO () Source
Render a string of text in the current font.
fgetFontError :: Font -> IO CInt Source
getFontError :: Font -> IO Int Source
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 -> String -> IO () Source
Render a string of text within a layout.
fgetLayoutError :: Layout -> IO CInt Source
getLayoutError :: Layout -> IO CInt Source
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
data TextAlignment Source
In a Layout directed render, the layout mode of the text
data GlyphOpaque Source
An opaque type encapsulating a glyph in C. Currently the glyph functions are unimplemented in Haskell.
data FontOpaque Source
An opaque type encapsulating a font in C.
data LayoutOpaque Source
An opaque type encapsulating a layout in C
type Glyph = Ptr GlyphOpaque Source
type Font = Ptr FontOpaque Source
type Layout = Ptr LayoutOpaque Source
marshalCharMap :: CharMap -> CInt Source