Safe Haskell | None |
---|---|
Language | Haskell2010 |
Rendering bitmap text with pcf-font is easy. Consider a program for rendering text into a PNG:
import Codec.Picture.Png import Codec.Picture.Types import Data.List import Graphics.Text.PCF import System.Environment -- | USAGE: program <font.pcf> <output.png> <text> main :: IO () main = do [input_file, output_file, text] <- getArgs pcf <- either fail return =<< loadPCF input_file case renderPCFText pcf text of Just (w, h, image_data) -> writePng output_file (Image w h image_data :: Image Pixel8) Nothing -> putStrLn "ERROR: Unable to render input text."
- loadPCF :: FilePath -> IO (Either String PCF)
- decodePCF :: ByteString -> Either String PCF
- renderPCFText :: PCF -> String -> Maybe (Int, Int, Vector Word8)
- getPCFGlyph :: PCF -> Char -> Maybe PCFGlyph
- getPCFGlyphPixel :: PCFGlyph -> Int -> Int -> Bool
- foldPCFGlyphPixels :: PCFGlyph -> (Int -> Int -> Bool -> a -> a) -> a -> a
- getPCFProps :: PCF -> [(ByteString, Either ByteString Int)]
- getGlyphStrings :: PCF -> [ByteString]
- data PCF
- data PCFGlyph = PCFGlyph {}
- data Metrics = Metrics {}
Decoding
loadPCF :: FilePath -> IO (Either String PCF) Source #
Load a PCF font file. File should not be compressed (e.g. ".pcf.gz" extension).
decodePCF :: ByteString -> Either String PCF Source #
Decode a PCF font from an in-memory ByteString
.
Rendering
:: PCF | Font to render with |
-> String | Text to render |
-> Maybe (Int, Int, Vector Word8) |
|
Generate a vector of black and white pixels from a PCF font and a string.
:: PCFGlyph | |
-> Int | X |
-> Int | Y |
-> Bool |
|
Calculate the color of a pixel in a glyph given its (x,y) coordinates.
:: PCFGlyph | |
-> (Int -> Int -> Bool -> a -> a) | Function that takes x, y, pixel value at (x,y), and an accumulator, returning a modified accumulator |
-> a | Initial accumulator |
-> a |
Scan over every pixel in a glyph, constructing some value in the process.
Metadata
getPCFProps :: PCF -> [(ByteString, Either ByteString Int)] Source #
List key-value pairs found in PCF properties table.
getGlyphStrings :: PCF -> [ByteString] Source #
Types
Container of a single glyph bitmap and its metadata.
PCFGlyph | |
|