| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
DearImGui.FontAtlas
Description
Font atlas builder, accompanied with lower-level functions.
import qualified DearImGui.FontAtlas as FontAtlas
prepareAtlas =
FontAtlas.rebuild
[ FontAtlas.FileTTF "comic-sans-mono.ttf" 13 csOptions csRanges
, FontAtlas.Default
]
where
csOptions = mconcat
[ FontAtlas.fontNo 1
, FontAtlas.glyphOffset (0, -1)
]
csRanges = RangeBuilder $ mconcat
[ FontAtlas.addText "Hello world"
, FontRanges.addChar Ꙑ
, FontRanges.addRanges FontRanges.Korean
]
Synopsis
- newtype Font = Font (Ptr ImFont)
- data FontSource
- rebuild :: (MonadIO m, Traversable t) => t FontSource -> m (t Font)
- newtype ConfigSetup = ConfigSetup {
- applyToConfig :: FontConfig -> IO ()
- fontDataOwnedByAtlas :: Bool -> ConfigSetup
- fontNo :: Int -> ConfigSetup
- sizePixels :: Float -> ConfigSetup
- oversampleH :: Int -> ConfigSetup
- oversampleV :: Int -> ConfigSetup
- pixelSnapH :: Bool -> ConfigSetup
- glyphExtraSpacing :: (Float, Float) -> ConfigSetup
- glyphOffset :: (Float, Float) -> ConfigSetup
- glyphRanges :: GlyphRanges -> ConfigSetup
- glyphMinAdvanceX :: Float -> ConfigSetup
- glyphMaxAdvanceX :: Float -> ConfigSetup
- mergeMode :: Bool -> ConfigSetup
- fontBuilderFlags :: Int -> ConfigSetup
- rasterizerMultiply :: Float -> ConfigSetup
- ellipsisChar :: ImWchar -> ConfigSetup
- data Ranges
- newtype RangesBuilderSetup = RangesBuilderSetup {
- applyToBuilder :: GlyphRangesBuilder -> IO ()
- addChar :: ImWchar -> RangesBuilderSetup
- addText :: Text -> RangesBuilderSetup
- addRanges :: Ranges -> RangesBuilderSetup
- addRangesRaw :: GlyphRanges -> RangesBuilderSetup
- pattern Latin :: Ranges
- pattern Korean :: Ranges
- pattern Japanese :: Ranges
- pattern ChineseFull :: Ranges
- pattern ChineseSimplifiedCommon :: Ranges
- pattern Cyrillic :: Ranges
- pattern Thai :: Ranges
- pattern Vietnamese :: Ranges
- build :: MonadIO m => m ()
- clear :: MonadIO m => m ()
- setupFont :: MonadManaged m => FontSource -> m Font
- setupRanges :: MonadManaged m => Ranges -> m (Maybe GlyphRanges)
- withRanges :: MonadUnliftIO m => RangesBuilderSetup -> (GlyphRanges -> m a) -> m a
- withConfig :: MonadUnliftIO m => Maybe ConfigSetup -> (Maybe FontConfig -> m a) -> m a
- addFontFromFileTTF :: MonadIO m => FilePath -> Float -> Maybe FontConfig -> Maybe GlyphRanges -> m (Maybe Font)
- addFontFromFileTTF_ :: MonadIO m => FilePath -> Float -> m (Maybe Font)
Main types
data FontSource Source #
Font setup data
Constructors
| DefaultFont | |
| FromTTF FilePath Float (Maybe ConfigSetup) Ranges |
Building atlas
rebuild :: (MonadIO m, Traversable t) => t FontSource -> m (t Font) Source #
Rebuild font atlas with provided configuration
and return corresponding structure of font handles
to be used with withFont.
Accepts any Traversable instance, so you are free to use
lists, maps or custom structures.
Configuring sources
newtype ConfigSetup Source #
Font config monoid interface to be used in FontSource.
mergeMode True <> fontNo 1
Constructors
| ConfigSetup | |
Fields
| |
Instances
| Monoid ConfigSetup Source # | |
Defined in DearImGui.FontAtlas Methods mempty :: ConfigSetup # mappend :: ConfigSetup -> ConfigSetup -> ConfigSetup # mconcat :: [ConfigSetup] -> ConfigSetup # | |
| Semigroup ConfigSetup Source # | |
Defined in DearImGui.FontAtlas Methods (<>) :: ConfigSetup -> ConfigSetup -> ConfigSetup # sconcat :: NonEmpty ConfigSetup -> ConfigSetup # stimes :: Integral b => b -> ConfigSetup -> ConfigSetup # | |
fontDataOwnedByAtlas :: Bool -> ConfigSetup Source #
TTF/OTF data ownership taken by the container ImFontAtlas (will delete memory itself).
By default, it is true
fontNo :: Int -> ConfigSetup Source #
Index of font within TTF/OTF file.
By default, it is 0
sizePixels :: Float -> ConfigSetup Source #
Size in pixels for rasterizer
More or less maps to the resulting font height.
Implicitly set by addFont... functions.
oversampleH :: Int -> ConfigSetup Source #
Rasterize at higher quality for sub-pixel positioning.
Note: the difference between 2 and 3 is minimal so you can reduce this to 2 to save memory. Read https://github.com/nothings/stb/blob/master/tests/oversample/README.md for details.
By default, it is 3
oversampleV :: Int -> ConfigSetup Source #
Rasterize at higher quality for sub-pixel positioning.
This is not really useful as we don't use sub-pixel positions on the Y axis.
By default, it is 1
pixelSnapH :: Bool -> ConfigSetup Source #
Align every glyph to pixel boundary.
Useful if you are merging a non-pixel aligned font with the default font. If enabled, you can set OversampleH/V to 1.
By default, it is false
glyphExtraSpacing :: (Float, Float) -> ConfigSetup Source #
Extra spacing (in pixels) between glyphs.
Only X axis is supported for now.
By default, it is 0, 0
glyphOffset :: (Float, Float) -> ConfigSetup Source #
Offset all glyphs from this font input.
By default, it is 0, 0
glyphRanges :: GlyphRanges -> ConfigSetup Source #
Pointer to a user-provided list of Unicode range.
2 values per range, inclusive. Zero-terminated list.
THE ARRAY DATA NEEDS TO PERSIST AS LONG AS THE FONT IS ALIVE.
By default, it is NULL
glyphMinAdvanceX :: Float -> ConfigSetup Source #
Minimum AdvanceX for glyphs.
Set Min to align font icons, set both Min/Max to enforce mono-space font.
By default, it is 0
glyphMaxAdvanceX :: Float -> ConfigSetup Source #
Maximum AdvanceX for glyphs.
By default, it is FLT_MAX.
mergeMode :: Bool -> ConfigSetup Source #
Merge into previous ImFont, so you can combine multiple inputs font into one ImFont.
e.g. ASCII font + icons + Japanese glyphs.
You may want to use GlyphOffset.y when merging font of different heights.
By default, it is false
fontBuilderFlags :: Int -> ConfigSetup Source #
Settings for custom font GlyphRanges.
THIS IS BUILDER IMPLEMENTATION DEPENDENT.
By default, it is 0. Leave it so if unsure.
rasterizerMultiply :: Float -> ConfigSetup Source #
Brighten (>1.0f) or darken (<1.0f) font output.
Brightening small fonts may be a good workaround to make them more readable.
By default, it is 1.0f.
ellipsisChar :: ImWchar -> ConfigSetup Source #
Explicitly specify unicode codepoint of ellipsis character.
When fonts are being merged first specified ellipsis will be used.
By default, it is -1
Configuring ranges
Glyph ranges settings, from presets to builder configuration.
newtype RangesBuilderSetup Source #
Ranges builder monoid interface to be executed through buildRanges.
addRanges FontRanges.DefaultRanges <> addText Привет
Constructors
| RangesBuilderSetup | |
Fields
| |
Instances
| Monoid RangesBuilderSetup Source # | |
Defined in DearImGui.FontAtlas Methods mempty :: RangesBuilderSetup # mappend :: RangesBuilderSetup -> RangesBuilderSetup -> RangesBuilderSetup # mconcat :: [RangesBuilderSetup] -> RangesBuilderSetup # | |
| Semigroup RangesBuilderSetup Source # | |
Defined in DearImGui.FontAtlas Methods (<>) :: RangesBuilderSetup -> RangesBuilderSetup -> RangesBuilderSetup # sconcat :: NonEmpty RangesBuilderSetup -> RangesBuilderSetup # stimes :: Integral b => b -> RangesBuilderSetup -> RangesBuilderSetup # | |
addChar :: ImWchar -> RangesBuilderSetup Source #
Single Unicode character
addText :: Text -> RangesBuilderSetup Source #
UTF-8 string
addRanges :: Ranges -> RangesBuilderSetup Source #
Existing ranges (through settings interface)
addRangesRaw :: GlyphRanges -> RangesBuilderSetup Source #
Existing ranges (as is)
pattern Japanese :: Ranges Source #
Default + Hiragana, Katakana, Half-Width, Selection of 2999 Ideographs
pattern ChineseFull :: Ranges Source #
Default + Half-Width + Japanese Hiragana/Katakana + full set of about 21000 CJK Unified Ideographs
pattern ChineseSimplifiedCommon :: Ranges Source #
Default + Half-Width + Japanese Hiragana/Katakana + set of 2500 CJK Unified Ideographs for common simplified Chinese
pattern Vietnamese :: Ranges Source #
Default + Vietnamese characters
Lower level types and functions
build :: MonadIO m => m () Source #
Build font atlas
Alias for buildFontAtlas
clear :: MonadIO m => m () Source #
Reset font atlas, clearing internal data
Alias for clearFontAtlas
setupFont :: MonadManaged m => FontSource -> m Font Source #
Load a font with provided configuration, return its handle and defer range builder and config destructors, if needed.
setupRanges :: MonadManaged m => Ranges -> m (Maybe GlyphRanges) Source #
Configure glyph ranges with provided configuration, return a handle and defer builder destructors, if needed.
withRanges :: MonadUnliftIO m => RangesBuilderSetup -> (GlyphRanges -> m a) -> m a Source #
Perform glyph ranges build based on provided configuration, and execute a computation with built glyph ranges.
withConfig :: MonadUnliftIO m => Maybe ConfigSetup -> (Maybe FontConfig -> m a) -> m a Source #
Configure font config with provided setup, and execute a computation with built object. return its handle and list of resource destructors.
Arguments
| :: MonadIO m | |
| => FilePath | Font file path |
| -> Float | Font size in pixels |
| -> Maybe FontConfig | Configuration data |
| -> Maybe GlyphRanges | Glyph ranges to use |
| -> m (Maybe Font) | Returns font handle, if added successfully |
Load a font from TTF file.
Specify font path and atlas glyph size.
Use addFontDefault if you want to retain built-in font too.
Call build after adding all the fonts,
particularly if you're loading them from memory or use custom glyphs.
Or stick to rebuild function.
Call backend-specific CreateFontsTexture before using newFrame.