module Graphics.Text.PCF.Types (
PCF(..),
PCFGlyph(..),
Prop(..),
Table(..),
Metrics(..),
TableMeta(..),
PCFTableType(..),
PCFText(..),
glyph_ascii,
glyph_ascii_lines,
pcf_text_string,
pcf_text_ascii
) where
import Data.Binary
import Data.Bits
import Data.Int
import Data.Monoid
import Data.List
import Data.Vector (Vector)
import Data.IntMap (IntMap)
import Data.ByteString.Lazy.Char8 (ByteString)
import qualified Data.ByteString.Lazy as B (concatMap, take)
import qualified Data.ByteString.Lazy.Char8 as B (unpack, splitAt, intercalate, concat)
import qualified Data.Vector.Storable as VS
data PCF = PCF { pcf_properties :: (TableMeta, Table)
, pcf_metrics :: (TableMeta, Table)
, pcf_bitmaps :: (TableMeta, Table)
, pcf_bdf_encodings :: (TableMeta, Table)
, pcf_swidths :: (TableMeta, Table)
, pcf_accelerators :: (TableMeta, Table)
, pcf_glyph_names :: Maybe (TableMeta, Table)
, pcf_ink_metrics :: Maybe (TableMeta, Table)
}
data Table = PROPERTIES { properties_props :: [Prop]
, properties_strings :: ByteString }
| BITMAPS { bitmaps_glyph_count :: Word32
, bitmaps_offsets :: Vector Word32
, bitmaps_sizes :: (Word32, Word32, Word32, Word32)
, bitmaps_data :: ByteString }
| METRICS { metrics_ink_type :: Bool
, metrics_compressed :: Bool
, metrics_metrics :: Vector Metrics }
| SWIDTHS { swidths_swidths :: [Word32] }
| ACCELERATORS { accel_no_overlap :: Bool
, accel_constant_metrics :: Bool
, accel_terminal_font :: Bool
, accel_constant_width :: Bool
, accel_ink_inside :: Bool
, accel_ink_metrics :: Bool
, accel_draw_direction :: Bool
, accel_font_ascent :: Word32
, accel_font_descent :: Word32
, accel_max_overlap :: Word32
, accel_min_bounds :: Metrics
, accel_max_bounds :: Metrics
, accel_ink_min_max_bounds :: Maybe (Metrics, Metrics)
}
| GLYPH_NAMES { glyph_names_offsets :: [Word32]
, glyph_names_string :: ByteString }
| BDF_ENCODINGS { encodings_cols :: (Word16, Word16)
, encodings_rows :: (Word16, Word16)
, encodings_default_char :: Word16
, encodings_glyph_indices :: IntMap Word16 }
data Prop = Prop { prop_name_offset :: Word32
, prop_is_string :: Word8
, prop_value :: Word32 }
deriving (Eq)
data Metrics = Metrics { metrics_left_sided_bearings :: Int16
, metrics_right_sided_bearings :: Int16
, metrics_character_width :: Int16
, metrics_character_ascent :: Int16
, metrics_character_descent :: Int16
, metrics_character_attributes :: Int16 }
deriving (Eq, Show)
data TableMeta = TableMeta { tableMetaType :: PCFTableType
, tableMetaFormat :: Word32
, tableMetaGlyphPad :: Word8
, tableMetaScanUnit :: Word8
, tableMetaByte :: Bool
, tableMetaBit :: Bool
, tableMetaSize :: Word32
, tableMetaOffset :: Word32
}
data PCFTableType = PCF_PROPERTIES
| PCF_ACCELERATORS
| PCF_METRICS
| PCF_BITMAPS
| PCF_INK_METRICS
| PCF_BDF_ENCODINGS
| PCF_SWIDTHS
| PCF_GLYPH_NAMES
| PCF_BDF_ACCELERATORS
deriving (Eq, Ord, Show)
data PCFGlyph = PCFGlyph { glyph_metrics :: Metrics
, glyph_char :: Char
, glyph_width :: Int
, glyph_height :: Int
, glyph_pitch :: Int
, glyph_bitmap :: ByteString
}
instance Show PCFGlyph where
show g@PCFGlyph{..} = "PCFGlyph {glyph_metrics = " ++ show glyph_metrics ++
", glyph_char = " ++ show glyph_char ++
", glyph_width = " ++ show glyph_width ++
", glyph_height = " ++ show glyph_height ++
", glyph_pitch = " ++ show glyph_pitch ++
", glyph_bitmap = " ++ show glyph_bitmap ++ "}\n" ++
glyph_ascii g
glyph_ascii :: PCFGlyph -> String
glyph_ascii = B.unpack . mconcat . map (<> "\n") . glyph_ascii_lines_bs
glyph_ascii_lines :: PCFGlyph -> [String]
glyph_ascii_lines = map B.unpack . glyph_ascii_lines_bs
glyph_ascii_lines_bs :: PCFGlyph -> [ByteString]
glyph_ascii_lines_bs PCFGlyph{..} = map (B.take (fromIntegral glyph_width) . showBits) rs
where
rs = rows glyph_bitmap
rows bs = case B.splitAt (fromIntegral glyph_pitch) bs of
(r, "") -> [r]
(r, t) -> r : rows t
showBits = B.concatMap $ mconcat $ map showBit [7,6..0]
showBit :: Int -> Word8 -> ByteString
showBit i w
| testBit w i = "X"
| otherwise = " "
data PCFText = PCFText { pcf_text_glyphs :: [PCFGlyph]
, pcf_text_width :: Int
, pcf_text_height :: Int
, pcf_text_image :: VS.Vector Word8
}
pcf_text_string :: PCFText -> String
pcf_text_string = map glyph_char . pcf_text_glyphs
pcf_text_ascii :: PCFText -> String
pcf_text_ascii = B.unpack . B.intercalate "\n" . map B.concat . transpose . map glyph_ascii_lines_bs . pcf_text_glyphs