Copyright | (c) 2018 Francisco Vallarino (c) 2016 Moritz Kiefer |
---|---|
License | BSD-3-Clause (see the LICENSE file) |
Maintainer | fjvallarino@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Provides functions for getting text dimensions and metrics.
Based on code from cocreature's https://github.com/cocreature/nanovg-hs
Synopsis
- data V4 a = V4 !a !a !a !a
- newtype Bounds = Bounds (V4 CFloat)
- data GlyphPosition = GlyphPosition {
- str :: !(Ptr CChar)
- glyphX :: !CFloat
- glyphPosMinX :: !CFloat
- glyphPosMaxX :: !CFloat
- glyphPosMinY :: !CFloat
- glyphPosMaxY :: !CFloat
- type GlyphPositionPtr = Ptr GlyphPosition
- peekBounds :: Ptr CFloat -> IO Bounds
- allocaBounds :: (Ptr CFloat -> IO b) -> IO b
- withCString :: Text -> (CString -> IO b) -> IO b
- withText :: Text -> (CString -> IO b) -> IO b
- withNull :: (Ptr a -> b) -> b
- type CUStringLen = (Ptr CUChar, CInt)
- useAsCUStringLen :: ByteString -> (CUStringLen -> IO a) -> IO a
- allocCUStringLen :: ByteString -> (CUStringLen -> IO a) -> IO a
- copyCUStringLenMemory :: CUStringLen -> IO CUStringLen
- newtype FMContext = FMContext (Ptr FMContext)
- fmInit :: Double -> IO FMContext
- fmCreateFont :: FMContext -> Text -> Text -> IO Int
- fmCreateFontMem :: FMContext -> Text -> ByteString -> IO Int
- fmSetScale :: FMContext -> Double -> IO ()
- fmFontFace :: FMContext -> Text -> IO ()
- fmFontSize :: FMContext -> Double -> IO ()
- fmFontBlur :: FMContext -> Double -> IO ()
- fmTextLetterSpacing :: FMContext -> Double -> IO ()
- fmTextLineHeight :: FMContext -> Double -> IO ()
- fmTextMetrics_ :: FMContext -> IO (CFloat, CFloat, CFloat)
- fmTextMetrics :: FMContext -> IO (Double, Double, Double)
- fmTextBounds_ :: FMContext -> Double -> Double -> Text -> IO (Double, Bounds)
- fmTextBounds :: FMContext -> Double -> Double -> Text -> IO (Double, Double, Double, Double)
- fmTextGlyphPositions_ :: FMContext -> Double -> Double -> Ptr CChar -> Ptr CChar -> GlyphPositionPtr -> CInt -> IO CInt
- fmTextGlyphPositions :: FMContext -> Double -> Double -> Text -> IO (Seq GlyphPosition)
- fmInit'_ :: CFloat -> IO FMContext
- fmCreateFont'_ :: FMContext -> Ptr CChar -> Ptr CChar -> IO CInt
- fmCreateFontMem'_ :: FMContext -> Ptr CChar -> Ptr CUChar -> CInt -> IO CInt
- fmSetScale'_ :: FMContext -> CFloat -> IO ()
- fmFontFace'_ :: FMContext -> Ptr CChar -> IO ()
- fmFontSize'_ :: FMContext -> CFloat -> IO ()
- fmFontBlur'_ :: FMContext -> CFloat -> IO ()
- fmTextLetterSpacing'_ :: FMContext -> CFloat -> IO ()
- fmTextLineHeight'_ :: FMContext -> CFloat -> IO ()
- fmTextMetrics_'_ :: FMContext -> Ptr CFloat -> Ptr CFloat -> Ptr CFloat -> IO ()
- fmTextBounds_'_ :: FMContext -> CFloat -> CFloat -> Ptr CChar -> Ptr CChar -> Ptr CFloat -> IO CFloat
- fmTextGlyphPositions_'_ :: FMContext -> CFloat -> CFloat -> Ptr CChar -> Ptr CChar -> GlyphPositionPtr -> CInt -> IO CInt
Documentation
Vector of 4 strict elements.
V4 !a !a !a !a |
Bounds of a block of text.
Instances
Storable Bounds Source # | |
Read Bounds Source # | |
Show Bounds Source # | |
Eq Bounds Source # | |
Ord Bounds Source # | |
data GlyphPosition Source #
Position of a glyph in a text string.
GlyphPosition | |
|
Instances
type GlyphPositionPtr = Ptr GlyphPosition Source #
type CUStringLen = (Ptr CUChar, CInt) Source #
Same as CStringLen, but for strings of unsigned char* array type.
useAsCUStringLen :: ByteString -> (CUStringLen -> IO a) -> IO a Source #
Same as useAsCStringLen
, but works with unsigned char* arrays.
allocCUStringLen :: ByteString -> (CUStringLen -> IO a) -> IO a Source #
Same as useAsCUStringLen
, but copies the underlying memory, leaving freeing it to the C code.
copyCUStringLenMemory :: CUStringLen -> IO CUStringLen Source #
Copy memory under given pointer to a new address. The allocated memory is not garbage-collected and needs to be freed manually later.
Instances
Storable FMContext Source # | |
Defined in Monomer.Graphics.FFI |
fmCreateFontMem :: FMContext -> Text -> ByteString -> IO Int Source #
fmTextBounds :: FMContext -> Double -> Double -> Text -> IO (Double, Double, Double, Double) Source #
fmTextGlyphPositions_ :: FMContext -> Double -> Double -> Ptr CChar -> Ptr CChar -> GlyphPositionPtr -> CInt -> IO CInt Source #
fmTextGlyphPositions :: FMContext -> Double -> Double -> Text -> IO (Seq GlyphPosition) Source #