Safe Haskell | None |
---|---|
Language | Haskell2010 |
Graphics.Rendering.MiniTypeset.FontTexture
Description
Store font glyphs in OpenGL textures
TODO: add (optional) subpixel rendering support (pre-render say 4 versions of the same glyphs with fractional horizontal offsets)
Synopsis
- replacementCharacter :: Char
- data BufLoc = BufLoc {
- _locGlyph :: !Glyph
- _locBufIdx :: !Int
- _locBufXY :: !(Int, Int)
- _locBufSiz :: !(Int, Int)
- _locBufOfs :: !(Int, Int)
- _locHM :: !(HorizontalMetrics Float)
- data TexBuf = TexBuf {
- _bufTexObj :: !TextureObject
- _bufSize :: !(Int, Int)
- allocateTexBuf :: FontTexture -> IO TexBuf
- data TexCursor = TexCursor {}
- zeroCursor :: TexCursor
- data FontTexture = FontTexture {
- _ftexFont :: !Font
- _ftexName :: !String
- _ftexHeight :: !(Float, Float)
- _ftexScaling :: !Scaling
- _ftexVM :: !(VerticalMetrics Float)
- _ftexChars :: !(UnicodeCache (Maybe BufLoc))
- _ftexBufSize :: !(Int, Int)
- _ftexCursor :: !(IORef TexCursor)
- _ftexBufs :: !(IORef [TexBuf])
- _ftexLGapFactor :: !Double
- scaleU :: Float -> Unscaled -> Float
- defaultTextureSize :: (Int, Int)
- newFontTexture :: Font -> Float -> String -> IO FontTexture
- newFontTexture' :: Font -> (Float, Float) -> String -> (Int, Int) -> Double -> IO FontTexture
- lookupFontTexture :: FontTexture -> Char -> IO BufLoc
- mbLookupFontTexture :: FontTexture -> Char -> IO (Maybe BufLoc)
- testRenderFullTextureQuad :: FontTexture -> Int -> IO ()
Documentation
The location of a glyph in a font texture collection
Constructors
BufLoc | |
Fields
|
A single texture buffer
Constructors
TexBuf | |
Fields
|
allocateTexBuf :: FontTexture -> IO TexBuf Source #
Constructors
TexCursor | |
data FontTexture Source #
A font texture collection: possibly several textures containing bitmaps a given font with a given height.
Constructors
FontTexture | |
Fields
|
Instances
Show FontTexture Source # | |
Defined in Graphics.Rendering.MiniTypeset.FontTexture Methods showsPrec :: Int -> FontTexture -> ShowS # show :: FontTexture -> String # showList :: [FontTexture] -> ShowS # |
defaultTextureSize :: (Int, Int) Source #
newFontTexture :: Font -> Float -> String -> IO FontTexture Source #
newFontTexture' :: Font -> (Float, Float) -> String -> (Int, Int) -> Double -> IO FontTexture Source #
Creates a new (empty) font texture. We allow different horizontal and vertical scaling, but both are measured in pixel heights
lookupFontTexture :: FontTexture -> Char -> IO BufLoc Source #
Finds a character in the font texture (rendering it first if necessary). If the glyph is not present in the font, we return the "replacement character" instead. If that doesn't exist either, then we return the "not defined glyph" (glyph #0)
mbLookupFontTexture :: FontTexture -> Char -> IO (Maybe BufLoc) Source #
Finds a character in the font texture (rendering it first if necessary)
testRenderFullTextureQuad :: FontTexture -> Int -> IO () Source #
Renders the given font texture as a quad (useful for debugging)