Safe Haskell | None |
---|---|
Language | Haskell2010 |
Rendering bitmap text with pcf-font is easy. For instance, a program that renders text into a PNG is trivial:
import Codec.Picture.Png import Codec.Picture.Types import Data.List import Graphics.Text.PCF import System.Environment -- | USAGE: program <font.pcf.gz> <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 (PCFText _ w h img) -> writePng output_file (Image w h img :: Image Pixel8) Nothing -> putStrLn "ERROR: Unable to render input text."
Rendering some text as an ASCII bitmap is also convenient:
import Graphics.Text.PCF import System.Environment -- | USAGE: program <font.pcf.gz> <text> main :: IO () main = do [font_file, text] <- getArgs pcf <- either fail return =<< loadPCF font_file case renderPCFText pcf text of Just pcf_text -> putStrLn $ pcf_text_ascii pcf_text Nothing -> putStrLn "ERROR: Unable to render input text."
- loadPCF :: FilePath -> IO (Either String PCF)
- decodePCF :: ByteString -> Either String PCF
- renderPCFText :: PCF -> String -> Maybe PCFText
- getPCFGlyph :: PCF -> Char -> Maybe PCFGlyph
- getPCFGlyphPixel :: PCFGlyph -> Int -> Int -> Bool
- foldPCFGlyphPixels :: PCFGlyph -> (Int -> Int -> Bool -> a -> a) -> a -> a
- pcf_text_ascii :: PCFText -> String
- glyph_ascii :: PCFGlyph -> String
- glyph_ascii_lines :: PCFGlyph -> [String]
- getPCFProps :: PCF -> [(ByteString, Either ByteString Int)]
- data PCF
- data PCFGlyph = PCFGlyph {}
- data PCFText = PCFText {}
- data Metrics = Metrics {}
Decoding
loadPCF :: FilePath -> IO (Either String PCF) Source #
Load a PCF font file. Both uncompressed and GZip compressed files are allowed, i.e. ".pcf" and ".pcf.gz" files.
decodePCF :: ByteString -> Either String PCF Source #
Decode a PCF font from an in-memory ByteString
. Uncompressed and GZip compressed input are allowed.
Rendering
:: PCF | Font to render with |
-> String | Text to render |
-> Maybe PCFText |
|
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.
ASCII Rendering
pcf_text_ascii :: PCFText -> String Source #
ASCII rendering of a whole PCFText string rendering.
glyph_ascii :: PCFGlyph -> String Source #
Render glyph bitmap as a string where X
represents opaque pixels and whitespace represents blank pixels.
glyph_ascii_lines :: PCFGlyph -> [String] Source #
Render glyph bitmap as a list of strings representing lines where X
represents opaque pixels and whitespace represents blank pixels.
Metadata
getPCFProps :: PCF -> [(ByteString, Either ByteString Int)] Source #
List key-value pairs found in PCF properties table.
Types
Container of a single glyph bitmap and its metadata.
PCFGlyph | |
|
Representation of string and its corresponding bitmap content. Metadata regarding source font is not included.
PCFText | |
|
Container of glyph dimension and position metrics.