pcf-font-0.2.2.1: PCF font parsing and rendering library.
Safe HaskellNone
LanguageHaskell2010

Graphics.Text.PCF

Description

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."
Synopsis

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

renderPCFText Source #

Arguments

:: PCF

Font to render with

-> String

Text to render

-> Maybe PCFText

Just width, height, and rendering; Nothing if an unrenderable character is encountered

Generate a vector of black and white pixels from a PCF font and a string. Black and white pixels are represented by 0x00 and 0xFF byte values respectively.

renderPCFTextColor Source #

Arguments

:: PCF

Font to render with

-> Word8

Opaque color value

-> Word8

Blank color value

-> String

Text to render

-> Maybe PCFText

Just width, height, and rendering; Nothing if an unrenderable character is encountered

Generate a vector of opaque and blank pixels from a PCF font and a string.

getPCFGlyph :: PCF -> Char -> Maybe PCFGlyph Source #

Extract a single glyph bitmap from a PCF font.

getPCFGlyphPixel Source #

Arguments

:: PCFGlyph 
-> Int

X

-> Int

Y

-> Bool

True if pixel at (x,y) is opaque; False if pixel at (x,y) is transparent or (x,y) is out of the glyph's bounds

Calculate the color of a pixel in a glyph given its (x,y) coordinates.

foldPCFGlyphPixels Source #

Arguments

:: 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

data PCF Source #

Container of tables extracted from a PCF font file.

data PCFGlyph Source #

Container of a single glyph bitmap and its metadata.

Constructors

PCFGlyph 

Fields

Instances

Instances details
Show PCFGlyph Source # 
Instance details

Defined in Graphics.Text.PCF.Types

data PCFText Source #

Representation of string and its corresponding bitmap content. Metadata regarding source font is not included.

Constructors

PCFText 

Fields

data Metrics Source #

Container of glyph dimension and position metrics.

Instances

Instances details
Eq Metrics Source # 
Instance details

Defined in Graphics.Text.PCF.Types

Methods

(==) :: Metrics -> Metrics -> Bool #

(/=) :: Metrics -> Metrics -> Bool #

Show Metrics Source # 
Instance details

Defined in Graphics.Text.PCF.Types