ktx-font
Safe HaskellNone
LanguageHaskell2010

Codec.Ktx2.Font

Synopsis

Documentation

capScalePlanes :: Float -> Compact -> Compact Source #

Rescale planes to caps height instead of ems.

pushBundleFont :: Context -> Bundle -> IO Int Source #

Put already-loaded font to context.

The context will NOT keep a fontData reference.

data Bundle Source #

Constructors

Bundle 

Fields

Instances

Instances details
Eq Bundle Source # 
Instance details

Defined in Codec.Ktx2.Font

Methods

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

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

Shaping contexts

data StackContext a Source #

Instances

Instances details
Functor StackContext Source # 
Instance details

Defined in Codec.Ktx2.Font

Methods

fmap :: (a -> b) -> StackContext a -> StackContext b #

(<$) :: a -> StackContext b -> StackContext a #

Foldable StackContext Source # 
Instance details

Defined in Codec.Ktx2.Font

Methods

fold :: Monoid m => StackContext m -> m #

foldMap :: Monoid m => (a -> m) -> StackContext a -> m #

foldMap' :: Monoid m => (a -> m) -> StackContext a -> m #

foldr :: (a -> b -> b) -> b -> StackContext a -> b #

foldr' :: (a -> b -> b) -> b -> StackContext a -> b #

foldl :: (b -> a -> b) -> b -> StackContext a -> b #

foldl' :: (b -> a -> b) -> b -> StackContext a -> b #

foldr1 :: (a -> a -> a) -> StackContext a -> a #

foldl1 :: (a -> a -> a) -> StackContext a -> a #

toList :: StackContext a -> [a] #

null :: StackContext a -> Bool #

length :: StackContext a -> Int #

elem :: Eq a => a -> StackContext a -> Bool #

maximum :: Ord a => StackContext a -> a #

minimum :: Ord a => StackContext a -> a #

sum :: Num a => StackContext a -> a #

product :: Num a => StackContext a -> a #

Traversable StackContext Source # 
Instance details

Defined in Codec.Ktx2.Font

Methods

traverse :: Applicative f => (a -> f b) -> StackContext a -> f (StackContext b) #

sequenceA :: Applicative f => StackContext (f a) -> f (StackContext a) #

mapM :: Monad m => (a -> m b) -> StackContext a -> m (StackContext b) #

sequence :: Monad m => StackContext (m a) -> m (StackContext a) #

Generic1 StackContext Source # 
Instance details

Defined in Codec.Ktx2.Font

Associated Types

type Rep1 StackContext 
Instance details

Defined in Codec.Ktx2.Font

type Rep1 StackContext = D1 ('MetaData "StackContext" "Codec.Ktx2.Font" "ktx-font-0.1.0.0-inplace" 'False) (C1 ('MetaCons "StackContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "shapeContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (MVar Context)) :*: (S1 ('MetaSel ('Just "bundled") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 IntMap) :*: S1 ('MetaSel ('Just "atlases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IntMap Compact)))))
Generic (StackContext a) Source # 
Instance details

Defined in Codec.Ktx2.Font

Associated Types

type Rep (StackContext a) 
Instance details

Defined in Codec.Ktx2.Font

type Rep (StackContext a) = D1 ('MetaData "StackContext" "Codec.Ktx2.Font" "ktx-font-0.1.0.0-inplace" 'False) (C1 ('MetaCons "StackContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "shapeContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (MVar Context)) :*: (S1 ('MetaSel ('Just "bundled") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IntMap a)) :*: S1 ('MetaSel ('Just "atlases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IntMap Compact)))))

Methods

from :: StackContext a -> Rep (StackContext a) x #

to :: Rep (StackContext a) x -> StackContext a #

type Rep1 StackContext Source # 
Instance details

Defined in Codec.Ktx2.Font

type Rep1 StackContext = D1 ('MetaData "StackContext" "Codec.Ktx2.Font" "ktx-font-0.1.0.0-inplace" 'False) (C1 ('MetaCons "StackContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "shapeContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (MVar Context)) :*: (S1 ('MetaSel ('Just "bundled") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 IntMap) :*: S1 ('MetaSel ('Just "atlases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IntMap Compact)))))
type Rep (StackContext a) Source # 
Instance details

Defined in Codec.Ktx2.Font

type Rep (StackContext a) = D1 ('MetaData "StackContext" "Codec.Ktx2.Font" "ktx-font-0.1.0.0-inplace" 'False) (C1 ('MetaCons "StackContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "shapeContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (MVar Context)) :*: (S1 ('MetaSel ('Just "bundled") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IntMap a)) :*: S1 ('MetaSel ('Just "atlases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IntMap Compact)))))

createStackContext :: Foldable t => t Bundle -> IO (StackContext ()) Source #

Create shaping context and push fonts from all the bundles.

mapWithBundle :: Foldable t => t (Bundle, a -> b) -> StackContext a -> StackContext b Source #

Update font annotations with the bundle collection annotated with update functions.

This may be used to attach more information, e.g. after all fonts were assigned texture slots.

The update collection should be a superset of what was initially bundled. Otherwise you may see missing things downstream.

destroyStackContext :: StackContext a -> IO () Source #

Destroy shaping context.

NB: Does NOT free the fonts as they may be shared with other stacks. Use freeBundle for that.