Copyright | Will Thompson and Iñaki García Etxebarria |
---|---|
License | LGPL-2.1 |
Maintainer | Iñaki García Etxebarria |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
- Signals
- BufferMessageFuncT
- DestroyFuncT
- FontGetGlyphAdvanceFuncT
- FontGetGlyphAdvancesFuncT
- FontGetGlyphContourPointFuncT
- FontGetGlyphFromNameFuncT
- FontGetGlyphFuncT
- FontGetGlyphKerningFuncT
- FontGetGlyphNameFuncT
- FontGetGlyphOriginFuncT
- FontGetNominalGlyphFuncT
- FontGetNominalGlyphsFuncT
- FontGetVariationGlyphFuncT
- ReferenceTableFuncT
- UnicodeCombiningClassFuncT
- UnicodeComposeFuncT
- UnicodeDecomposeCompatibilityFuncT
- UnicodeDecomposeFuncT
- UnicodeEastasianWidthFuncT
- UnicodeGeneralCategoryFuncT
- UnicodeMirroringFuncT
- UnicodeScriptFuncT
Synopsis
- type BufferMessageFuncT = BufferT -> FontT -> Text -> IO Int32
- type BufferMessageFuncT_WithClosures = BufferT -> FontT -> Text -> Ptr () -> IO Int32
- type C_BufferMessageFuncT = Ptr BufferT -> Ptr FontT -> CString -> Ptr () -> IO Int32
- drop_closures_BufferMessageFuncT :: BufferMessageFuncT -> BufferMessageFuncT_WithClosures
- dynamic_BufferMessageFuncT :: (HasCallStack, MonadIO m) => FunPtr C_BufferMessageFuncT -> BufferT -> FontT -> Text -> Ptr () -> m Int32
- genClosure_BufferMessageFuncT :: MonadIO m => BufferMessageFuncT -> m (GClosure C_BufferMessageFuncT)
- mk_BufferMessageFuncT :: C_BufferMessageFuncT -> IO (FunPtr C_BufferMessageFuncT)
- noBufferMessageFuncT :: Maybe BufferMessageFuncT
- noBufferMessageFuncT_WithClosures :: Maybe BufferMessageFuncT_WithClosures
- wrap_BufferMessageFuncT :: Maybe (Ptr (FunPtr C_BufferMessageFuncT)) -> BufferMessageFuncT_WithClosures -> C_BufferMessageFuncT
- type C_DestroyFuncT = Ptr () -> IO ()
- type DestroyFuncT = IO ()
- type DestroyFuncT_WithClosures = Ptr () -> IO ()
- drop_closures_DestroyFuncT :: DestroyFuncT -> DestroyFuncT_WithClosures
- dynamic_DestroyFuncT :: (HasCallStack, MonadIO m) => FunPtr C_DestroyFuncT -> Ptr () -> m ()
- genClosure_DestroyFuncT :: MonadIO m => DestroyFuncT -> m (GClosure C_DestroyFuncT)
- mk_DestroyFuncT :: C_DestroyFuncT -> IO (FunPtr C_DestroyFuncT)
- noDestroyFuncT :: Maybe DestroyFuncT
- noDestroyFuncT_WithClosures :: Maybe DestroyFuncT_WithClosures
- wrap_DestroyFuncT :: Maybe (Ptr (FunPtr C_DestroyFuncT)) -> DestroyFuncT_WithClosures -> C_DestroyFuncT
- type C_FontGetGlyphAdvanceFuncT = Ptr FontT -> Ptr () -> Word32 -> Ptr () -> IO Int32
- type FontGetGlyphAdvanceFuncT = FontT -> Ptr () -> Word32 -> IO Int32
- type FontGetGlyphAdvanceFuncT_WithClosures = FontT -> Ptr () -> Word32 -> Ptr () -> IO Int32
- drop_closures_FontGetGlyphAdvanceFuncT :: FontGetGlyphAdvanceFuncT -> FontGetGlyphAdvanceFuncT_WithClosures
- dynamic_FontGetGlyphAdvanceFuncT :: (HasCallStack, MonadIO m) => FunPtr C_FontGetGlyphAdvanceFuncT -> FontT -> Ptr () -> Word32 -> Ptr () -> m Int32
- genClosure_FontGetGlyphAdvanceFuncT :: MonadIO m => FontGetGlyphAdvanceFuncT -> m (GClosure C_FontGetGlyphAdvanceFuncT)
- mk_FontGetGlyphAdvanceFuncT :: C_FontGetGlyphAdvanceFuncT -> IO (FunPtr C_FontGetGlyphAdvanceFuncT)
- noFontGetGlyphAdvanceFuncT :: Maybe FontGetGlyphAdvanceFuncT
- noFontGetGlyphAdvanceFuncT_WithClosures :: Maybe FontGetGlyphAdvanceFuncT_WithClosures
- wrap_FontGetGlyphAdvanceFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphAdvanceFuncT)) -> FontGetGlyphAdvanceFuncT_WithClosures -> C_FontGetGlyphAdvanceFuncT
- type C_FontGetGlyphAdvancesFuncT = Ptr FontT -> Ptr () -> Word32 -> Word32 -> Word32 -> Ptr Int32 -> Word32 -> Ptr () -> IO ()
- type FontGetGlyphAdvancesFuncT = FontT -> Ptr () -> Word32 -> Word32 -> Word32 -> Word32 -> IO Int32
- type FontGetGlyphAdvancesFuncT_WithClosures = FontT -> Ptr () -> Word32 -> Word32 -> Word32 -> Word32 -> Ptr () -> IO Int32
- drop_closures_FontGetGlyphAdvancesFuncT :: FontGetGlyphAdvancesFuncT -> FontGetGlyphAdvancesFuncT_WithClosures
- dynamic_FontGetGlyphAdvancesFuncT :: (HasCallStack, MonadIO m) => FunPtr C_FontGetGlyphAdvancesFuncT -> FontT -> Ptr () -> Word32 -> Word32 -> Word32 -> Word32 -> Ptr () -> m Int32
- genClosure_FontGetGlyphAdvancesFuncT :: MonadIO m => FontGetGlyphAdvancesFuncT -> m (GClosure C_FontGetGlyphAdvancesFuncT)
- mk_FontGetGlyphAdvancesFuncT :: C_FontGetGlyphAdvancesFuncT -> IO (FunPtr C_FontGetGlyphAdvancesFuncT)
- noFontGetGlyphAdvancesFuncT :: Maybe FontGetGlyphAdvancesFuncT
- noFontGetGlyphAdvancesFuncT_WithClosures :: Maybe FontGetGlyphAdvancesFuncT_WithClosures
- wrap_FontGetGlyphAdvancesFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphAdvancesFuncT)) -> FontGetGlyphAdvancesFuncT_WithClosures -> C_FontGetGlyphAdvancesFuncT
- type C_FontGetGlyphContourPointFuncT = Ptr FontT -> Ptr () -> Word32 -> Word32 -> Ptr Int32 -> Ptr Int32 -> Ptr () -> IO Int32
- type FontGetGlyphContourPointFuncT = FontT -> Ptr () -> Word32 -> Word32 -> IO (Int32, Int32, Int32)
- type FontGetGlyphContourPointFuncT_WithClosures = FontT -> Ptr () -> Word32 -> Word32 -> Ptr () -> IO (Int32, Int32, Int32)
- drop_closures_FontGetGlyphContourPointFuncT :: FontGetGlyphContourPointFuncT -> FontGetGlyphContourPointFuncT_WithClosures
- dynamic_FontGetGlyphContourPointFuncT :: (HasCallStack, MonadIO m) => FunPtr C_FontGetGlyphContourPointFuncT -> FontT -> Ptr () -> Word32 -> Word32 -> Ptr () -> m (Int32, Int32, Int32)
- genClosure_FontGetGlyphContourPointFuncT :: MonadIO m => FontGetGlyphContourPointFuncT -> m (GClosure C_FontGetGlyphContourPointFuncT)
- mk_FontGetGlyphContourPointFuncT :: C_FontGetGlyphContourPointFuncT -> IO (FunPtr C_FontGetGlyphContourPointFuncT)
- noFontGetGlyphContourPointFuncT :: Maybe FontGetGlyphContourPointFuncT
- noFontGetGlyphContourPointFuncT_WithClosures :: Maybe FontGetGlyphContourPointFuncT_WithClosures
- wrap_FontGetGlyphContourPointFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphContourPointFuncT)) -> FontGetGlyphContourPointFuncT_WithClosures -> C_FontGetGlyphContourPointFuncT
- type C_FontGetGlyphFromNameFuncT = Ptr FontT -> Ptr () -> Ptr CString -> Int32 -> Ptr Word32 -> Ptr () -> IO Int32
- type FontGetGlyphFromNameFuncT = FontT -> Ptr () -> [Text] -> IO (Int32, Word32)
- type FontGetGlyphFromNameFuncT_WithClosures = FontT -> Ptr () -> [Text] -> Ptr () -> IO (Int32, Word32)
- drop_closures_FontGetGlyphFromNameFuncT :: FontGetGlyphFromNameFuncT -> FontGetGlyphFromNameFuncT_WithClosures
- dynamic_FontGetGlyphFromNameFuncT :: (HasCallStack, MonadIO m) => FunPtr C_FontGetGlyphFromNameFuncT -> FontT -> Ptr () -> [Text] -> Ptr () -> m (Int32, Word32)
- genClosure_FontGetGlyphFromNameFuncT :: MonadIO m => FontGetGlyphFromNameFuncT -> m (GClosure C_FontGetGlyphFromNameFuncT)
- mk_FontGetGlyphFromNameFuncT :: C_FontGetGlyphFromNameFuncT -> IO (FunPtr C_FontGetGlyphFromNameFuncT)
- noFontGetGlyphFromNameFuncT :: Maybe FontGetGlyphFromNameFuncT
- noFontGetGlyphFromNameFuncT_WithClosures :: Maybe FontGetGlyphFromNameFuncT_WithClosures
- wrap_FontGetGlyphFromNameFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphFromNameFuncT)) -> FontGetGlyphFromNameFuncT_WithClosures -> C_FontGetGlyphFromNameFuncT
- type C_FontGetGlyphFuncT = Ptr FontT -> Ptr () -> Word32 -> Word32 -> Ptr Word32 -> Ptr () -> IO Int32
- type FontGetGlyphFuncT = FontT -> Ptr () -> Word32 -> Word32 -> IO (Int32, Word32)
- type FontGetGlyphFuncT_WithClosures = FontT -> Ptr () -> Word32 -> Word32 -> Ptr () -> IO (Int32, Word32)
- drop_closures_FontGetGlyphFuncT :: FontGetGlyphFuncT -> FontGetGlyphFuncT_WithClosures
- dynamic_FontGetGlyphFuncT :: (HasCallStack, MonadIO m) => FunPtr C_FontGetGlyphFuncT -> FontT -> Ptr () -> Word32 -> Word32 -> Ptr () -> m (Int32, Word32)
- genClosure_FontGetGlyphFuncT :: MonadIO m => FontGetGlyphFuncT -> m (GClosure C_FontGetGlyphFuncT)
- mk_FontGetGlyphFuncT :: C_FontGetGlyphFuncT -> IO (FunPtr C_FontGetGlyphFuncT)
- noFontGetGlyphFuncT :: Maybe FontGetGlyphFuncT
- noFontGetGlyphFuncT_WithClosures :: Maybe FontGetGlyphFuncT_WithClosures
- wrap_FontGetGlyphFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphFuncT)) -> FontGetGlyphFuncT_WithClosures -> C_FontGetGlyphFuncT
- type C_FontGetGlyphKerningFuncT = Ptr FontT -> Ptr () -> Word32 -> Word32 -> Ptr () -> IO Int32
- type FontGetGlyphKerningFuncT = FontT -> Ptr () -> Word32 -> Word32 -> IO Int32
- type FontGetGlyphKerningFuncT_WithClosures = FontT -> Ptr () -> Word32 -> Word32 -> Ptr () -> IO Int32
- drop_closures_FontGetGlyphKerningFuncT :: FontGetGlyphKerningFuncT -> FontGetGlyphKerningFuncT_WithClosures
- dynamic_FontGetGlyphKerningFuncT :: (HasCallStack, MonadIO m) => FunPtr C_FontGetGlyphKerningFuncT -> FontT -> Ptr () -> Word32 -> Word32 -> Ptr () -> m Int32
- genClosure_FontGetGlyphKerningFuncT :: MonadIO m => FontGetGlyphKerningFuncT -> m (GClosure C_FontGetGlyphKerningFuncT)
- mk_FontGetGlyphKerningFuncT :: C_FontGetGlyphKerningFuncT -> IO (FunPtr C_FontGetGlyphKerningFuncT)
- noFontGetGlyphKerningFuncT :: Maybe FontGetGlyphKerningFuncT
- noFontGetGlyphKerningFuncT_WithClosures :: Maybe FontGetGlyphKerningFuncT_WithClosures
- wrap_FontGetGlyphKerningFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphKerningFuncT)) -> FontGetGlyphKerningFuncT_WithClosures -> C_FontGetGlyphKerningFuncT
- type C_FontGetGlyphNameFuncT = Ptr FontT -> Ptr () -> Word32 -> Ptr (Ptr CString) -> Ptr Word32 -> Ptr () -> IO Int32
- type FontGetGlyphNameFuncT = FontT -> Ptr () -> Word32 -> IO (Int32, [Text])
- type FontGetGlyphNameFuncT_WithClosures = FontT -> Ptr () -> Word32 -> Ptr () -> IO (Int32, [Text])
- drop_closures_FontGetGlyphNameFuncT :: FontGetGlyphNameFuncT -> FontGetGlyphNameFuncT_WithClosures
- dynamic_FontGetGlyphNameFuncT :: (HasCallStack, MonadIO m) => FunPtr C_FontGetGlyphNameFuncT -> FontT -> Ptr () -> Word32 -> Ptr () -> m (Int32, [Text])
- genClosure_FontGetGlyphNameFuncT :: MonadIO m => FontGetGlyphNameFuncT -> m (GClosure C_FontGetGlyphNameFuncT)
- mk_FontGetGlyphNameFuncT :: C_FontGetGlyphNameFuncT -> IO (FunPtr C_FontGetGlyphNameFuncT)
- noFontGetGlyphNameFuncT :: Maybe FontGetGlyphNameFuncT
- noFontGetGlyphNameFuncT_WithClosures :: Maybe FontGetGlyphNameFuncT_WithClosures
- wrap_FontGetGlyphNameFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphNameFuncT)) -> FontGetGlyphNameFuncT_WithClosures -> C_FontGetGlyphNameFuncT
- type C_FontGetGlyphOriginFuncT = Ptr FontT -> Ptr () -> Word32 -> Ptr Int32 -> Ptr Int32 -> Ptr () -> IO Int32
- type FontGetGlyphOriginFuncT = FontT -> Ptr () -> Word32 -> IO (Int32, Int32, Int32)
- type FontGetGlyphOriginFuncT_WithClosures = FontT -> Ptr () -> Word32 -> Ptr () -> IO (Int32, Int32, Int32)
- drop_closures_FontGetGlyphOriginFuncT :: FontGetGlyphOriginFuncT -> FontGetGlyphOriginFuncT_WithClosures
- dynamic_FontGetGlyphOriginFuncT :: (HasCallStack, MonadIO m) => FunPtr C_FontGetGlyphOriginFuncT -> FontT -> Ptr () -> Word32 -> Ptr () -> m (Int32, Int32, Int32)
- genClosure_FontGetGlyphOriginFuncT :: MonadIO m => FontGetGlyphOriginFuncT -> m (GClosure C_FontGetGlyphOriginFuncT)
- mk_FontGetGlyphOriginFuncT :: C_FontGetGlyphOriginFuncT -> IO (FunPtr C_FontGetGlyphOriginFuncT)
- noFontGetGlyphOriginFuncT :: Maybe FontGetGlyphOriginFuncT
- noFontGetGlyphOriginFuncT_WithClosures :: Maybe FontGetGlyphOriginFuncT_WithClosures
- wrap_FontGetGlyphOriginFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphOriginFuncT)) -> FontGetGlyphOriginFuncT_WithClosures -> C_FontGetGlyphOriginFuncT
- type C_FontGetNominalGlyphFuncT = Ptr FontT -> Ptr () -> Word32 -> Ptr Word32 -> Ptr () -> IO Int32
- type FontGetNominalGlyphFuncT = FontT -> Ptr () -> Word32 -> IO (Int32, Word32)
- type FontGetNominalGlyphFuncT_WithClosures = FontT -> Ptr () -> Word32 -> Ptr () -> IO (Int32, Word32)
- drop_closures_FontGetNominalGlyphFuncT :: FontGetNominalGlyphFuncT -> FontGetNominalGlyphFuncT_WithClosures
- dynamic_FontGetNominalGlyphFuncT :: (HasCallStack, MonadIO m) => FunPtr C_FontGetNominalGlyphFuncT -> FontT -> Ptr () -> Word32 -> Ptr () -> m (Int32, Word32)
- genClosure_FontGetNominalGlyphFuncT :: MonadIO m => FontGetNominalGlyphFuncT -> m (GClosure C_FontGetNominalGlyphFuncT)
- mk_FontGetNominalGlyphFuncT :: C_FontGetNominalGlyphFuncT -> IO (FunPtr C_FontGetNominalGlyphFuncT)
- noFontGetNominalGlyphFuncT :: Maybe FontGetNominalGlyphFuncT
- noFontGetNominalGlyphFuncT_WithClosures :: Maybe FontGetNominalGlyphFuncT_WithClosures
- wrap_FontGetNominalGlyphFuncT :: Maybe (Ptr (FunPtr C_FontGetNominalGlyphFuncT)) -> FontGetNominalGlyphFuncT_WithClosures -> C_FontGetNominalGlyphFuncT
- type C_FontGetNominalGlyphsFuncT = Ptr FontT -> Ptr () -> Word32 -> Word32 -> Word32 -> Ptr Word32 -> Word32 -> Ptr () -> IO Word32
- type FontGetNominalGlyphsFuncT = FontT -> Ptr () -> Word32 -> Word32 -> Word32 -> Word32 -> IO (Word32, Word32)
- type FontGetNominalGlyphsFuncT_WithClosures = FontT -> Ptr () -> Word32 -> Word32 -> Word32 -> Word32 -> Ptr () -> IO (Word32, Word32)
- drop_closures_FontGetNominalGlyphsFuncT :: FontGetNominalGlyphsFuncT -> FontGetNominalGlyphsFuncT_WithClosures
- dynamic_FontGetNominalGlyphsFuncT :: (HasCallStack, MonadIO m) => FunPtr C_FontGetNominalGlyphsFuncT -> FontT -> Ptr () -> Word32 -> Word32 -> Word32 -> Word32 -> Ptr () -> m (Word32, Word32)
- genClosure_FontGetNominalGlyphsFuncT :: MonadIO m => FontGetNominalGlyphsFuncT -> m (GClosure C_FontGetNominalGlyphsFuncT)
- mk_FontGetNominalGlyphsFuncT :: C_FontGetNominalGlyphsFuncT -> IO (FunPtr C_FontGetNominalGlyphsFuncT)
- noFontGetNominalGlyphsFuncT :: Maybe FontGetNominalGlyphsFuncT
- noFontGetNominalGlyphsFuncT_WithClosures :: Maybe FontGetNominalGlyphsFuncT_WithClosures
- wrap_FontGetNominalGlyphsFuncT :: Maybe (Ptr (FunPtr C_FontGetNominalGlyphsFuncT)) -> FontGetNominalGlyphsFuncT_WithClosures -> C_FontGetNominalGlyphsFuncT
- type C_FontGetVariationGlyphFuncT = Ptr FontT -> Ptr () -> Word32 -> Word32 -> Ptr Word32 -> Ptr () -> IO Int32
- type FontGetVariationGlyphFuncT = FontT -> Ptr () -> Word32 -> Word32 -> IO (Int32, Word32)
- type FontGetVariationGlyphFuncT_WithClosures = FontT -> Ptr () -> Word32 -> Word32 -> Ptr () -> IO (Int32, Word32)
- drop_closures_FontGetVariationGlyphFuncT :: FontGetVariationGlyphFuncT -> FontGetVariationGlyphFuncT_WithClosures
- dynamic_FontGetVariationGlyphFuncT :: (HasCallStack, MonadIO m) => FunPtr C_FontGetVariationGlyphFuncT -> FontT -> Ptr () -> Word32 -> Word32 -> Ptr () -> m (Int32, Word32)
- genClosure_FontGetVariationGlyphFuncT :: MonadIO m => FontGetVariationGlyphFuncT -> m (GClosure C_FontGetVariationGlyphFuncT)
- mk_FontGetVariationGlyphFuncT :: C_FontGetVariationGlyphFuncT -> IO (FunPtr C_FontGetVariationGlyphFuncT)
- noFontGetVariationGlyphFuncT :: Maybe FontGetVariationGlyphFuncT
- noFontGetVariationGlyphFuncT_WithClosures :: Maybe FontGetVariationGlyphFuncT_WithClosures
- wrap_FontGetVariationGlyphFuncT :: Maybe (Ptr (FunPtr C_FontGetVariationGlyphFuncT)) -> FontGetVariationGlyphFuncT_WithClosures -> C_FontGetVariationGlyphFuncT
- type C_ReferenceTableFuncT = Ptr FaceT -> Word32 -> Ptr () -> IO (Ptr BlobT)
- type ReferenceTableFuncT = FaceT -> Word32 -> IO BlobT
- type ReferenceTableFuncT_WithClosures = FaceT -> Word32 -> Ptr () -> IO BlobT
- drop_closures_ReferenceTableFuncT :: ReferenceTableFuncT -> ReferenceTableFuncT_WithClosures
- dynamic_ReferenceTableFuncT :: (HasCallStack, MonadIO m) => FunPtr C_ReferenceTableFuncT -> FaceT -> Word32 -> Ptr () -> m BlobT
- genClosure_ReferenceTableFuncT :: MonadIO m => ReferenceTableFuncT -> m (GClosure C_ReferenceTableFuncT)
- mk_ReferenceTableFuncT :: C_ReferenceTableFuncT -> IO (FunPtr C_ReferenceTableFuncT)
- noReferenceTableFuncT :: Maybe ReferenceTableFuncT
- noReferenceTableFuncT_WithClosures :: Maybe ReferenceTableFuncT_WithClosures
- wrap_ReferenceTableFuncT :: Maybe (Ptr (FunPtr C_ReferenceTableFuncT)) -> ReferenceTableFuncT_WithClosures -> C_ReferenceTableFuncT
- type C_UnicodeCombiningClassFuncT = Ptr UnicodeFuncsT -> Word32 -> Ptr () -> IO CUInt
- type UnicodeCombiningClassFuncT = UnicodeFuncsT -> Word32 -> IO UnicodeCombiningClassT
- type UnicodeCombiningClassFuncT_WithClosures = UnicodeFuncsT -> Word32 -> Ptr () -> IO UnicodeCombiningClassT
- drop_closures_UnicodeCombiningClassFuncT :: UnicodeCombiningClassFuncT -> UnicodeCombiningClassFuncT_WithClosures
- dynamic_UnicodeCombiningClassFuncT :: (HasCallStack, MonadIO m) => FunPtr C_UnicodeCombiningClassFuncT -> UnicodeFuncsT -> Word32 -> Ptr () -> m UnicodeCombiningClassT
- genClosure_UnicodeCombiningClassFuncT :: MonadIO m => UnicodeCombiningClassFuncT -> m (GClosure C_UnicodeCombiningClassFuncT)
- mk_UnicodeCombiningClassFuncT :: C_UnicodeCombiningClassFuncT -> IO (FunPtr C_UnicodeCombiningClassFuncT)
- noUnicodeCombiningClassFuncT :: Maybe UnicodeCombiningClassFuncT
- noUnicodeCombiningClassFuncT_WithClosures :: Maybe UnicodeCombiningClassFuncT_WithClosures
- wrap_UnicodeCombiningClassFuncT :: Maybe (Ptr (FunPtr C_UnicodeCombiningClassFuncT)) -> UnicodeCombiningClassFuncT_WithClosures -> C_UnicodeCombiningClassFuncT
- type C_UnicodeComposeFuncT = Ptr UnicodeFuncsT -> Word32 -> Word32 -> Ptr Word32 -> Ptr () -> IO Int32
- type UnicodeComposeFuncT = UnicodeFuncsT -> Word32 -> Word32 -> IO (Int32, Word32)
- type UnicodeComposeFuncT_WithClosures = UnicodeFuncsT -> Word32 -> Word32 -> Ptr () -> IO (Int32, Word32)
- drop_closures_UnicodeComposeFuncT :: UnicodeComposeFuncT -> UnicodeComposeFuncT_WithClosures
- dynamic_UnicodeComposeFuncT :: (HasCallStack, MonadIO m) => FunPtr C_UnicodeComposeFuncT -> UnicodeFuncsT -> Word32 -> Word32 -> Ptr () -> m (Int32, Word32)
- genClosure_UnicodeComposeFuncT :: MonadIO m => UnicodeComposeFuncT -> m (GClosure C_UnicodeComposeFuncT)
- mk_UnicodeComposeFuncT :: C_UnicodeComposeFuncT -> IO (FunPtr C_UnicodeComposeFuncT)
- noUnicodeComposeFuncT :: Maybe UnicodeComposeFuncT
- noUnicodeComposeFuncT_WithClosures :: Maybe UnicodeComposeFuncT_WithClosures
- wrap_UnicodeComposeFuncT :: Maybe (Ptr (FunPtr C_UnicodeComposeFuncT)) -> UnicodeComposeFuncT_WithClosures -> C_UnicodeComposeFuncT
- type C_UnicodeDecomposeCompatibilityFuncT = Ptr UnicodeFuncsT -> Word32 -> Word32 -> Ptr () -> IO Word32
- type UnicodeDecomposeCompatibilityFuncT = UnicodeFuncsT -> Word32 -> Word32 -> IO Word32
- type UnicodeDecomposeCompatibilityFuncT_WithClosures = UnicodeFuncsT -> Word32 -> Word32 -> Ptr () -> IO Word32
- drop_closures_UnicodeDecomposeCompatibilityFuncT :: UnicodeDecomposeCompatibilityFuncT -> UnicodeDecomposeCompatibilityFuncT_WithClosures
- dynamic_UnicodeDecomposeCompatibilityFuncT :: (HasCallStack, MonadIO m) => FunPtr C_UnicodeDecomposeCompatibilityFuncT -> UnicodeFuncsT -> Word32 -> Word32 -> Ptr () -> m Word32
- genClosure_UnicodeDecomposeCompatibilityFuncT :: MonadIO m => UnicodeDecomposeCompatibilityFuncT -> m (GClosure C_UnicodeDecomposeCompatibilityFuncT)
- mk_UnicodeDecomposeCompatibilityFuncT :: C_UnicodeDecomposeCompatibilityFuncT -> IO (FunPtr C_UnicodeDecomposeCompatibilityFuncT)
- noUnicodeDecomposeCompatibilityFuncT :: Maybe UnicodeDecomposeCompatibilityFuncT
- noUnicodeDecomposeCompatibilityFuncT_WithClosures :: Maybe UnicodeDecomposeCompatibilityFuncT_WithClosures
- wrap_UnicodeDecomposeCompatibilityFuncT :: Maybe (Ptr (FunPtr C_UnicodeDecomposeCompatibilityFuncT)) -> UnicodeDecomposeCompatibilityFuncT_WithClosures -> C_UnicodeDecomposeCompatibilityFuncT
- type C_UnicodeDecomposeFuncT = Ptr UnicodeFuncsT -> Word32 -> Ptr Word32 -> Ptr Word32 -> Ptr () -> IO Int32
- type UnicodeDecomposeFuncT = UnicodeFuncsT -> Word32 -> IO (Int32, Word32, Word32)
- type UnicodeDecomposeFuncT_WithClosures = UnicodeFuncsT -> Word32 -> Ptr () -> IO (Int32, Word32, Word32)
- drop_closures_UnicodeDecomposeFuncT :: UnicodeDecomposeFuncT -> UnicodeDecomposeFuncT_WithClosures
- dynamic_UnicodeDecomposeFuncT :: (HasCallStack, MonadIO m) => FunPtr C_UnicodeDecomposeFuncT -> UnicodeFuncsT -> Word32 -> Ptr () -> m (Int32, Word32, Word32)
- genClosure_UnicodeDecomposeFuncT :: MonadIO m => UnicodeDecomposeFuncT -> m (GClosure C_UnicodeDecomposeFuncT)
- mk_UnicodeDecomposeFuncT :: C_UnicodeDecomposeFuncT -> IO (FunPtr C_UnicodeDecomposeFuncT)
- noUnicodeDecomposeFuncT :: Maybe UnicodeDecomposeFuncT
- noUnicodeDecomposeFuncT_WithClosures :: Maybe UnicodeDecomposeFuncT_WithClosures
- wrap_UnicodeDecomposeFuncT :: Maybe (Ptr (FunPtr C_UnicodeDecomposeFuncT)) -> UnicodeDecomposeFuncT_WithClosures -> C_UnicodeDecomposeFuncT
- type C_UnicodeEastasianWidthFuncT = Ptr UnicodeFuncsT -> Word32 -> Ptr () -> IO Word32
- type UnicodeEastasianWidthFuncT = UnicodeFuncsT -> Word32 -> IO Word32
- type UnicodeEastasianWidthFuncT_WithClosures = UnicodeFuncsT -> Word32 -> Ptr () -> IO Word32
- drop_closures_UnicodeEastasianWidthFuncT :: UnicodeEastasianWidthFuncT -> UnicodeEastasianWidthFuncT_WithClosures
- dynamic_UnicodeEastasianWidthFuncT :: (HasCallStack, MonadIO m) => FunPtr C_UnicodeEastasianWidthFuncT -> UnicodeFuncsT -> Word32 -> Ptr () -> m Word32
- genClosure_UnicodeEastasianWidthFuncT :: MonadIO m => UnicodeEastasianWidthFuncT -> m (GClosure C_UnicodeEastasianWidthFuncT)
- mk_UnicodeEastasianWidthFuncT :: C_UnicodeEastasianWidthFuncT -> IO (FunPtr C_UnicodeEastasianWidthFuncT)
- noUnicodeEastasianWidthFuncT :: Maybe UnicodeEastasianWidthFuncT
- noUnicodeEastasianWidthFuncT_WithClosures :: Maybe UnicodeEastasianWidthFuncT_WithClosures
- wrap_UnicodeEastasianWidthFuncT :: Maybe (Ptr (FunPtr C_UnicodeEastasianWidthFuncT)) -> UnicodeEastasianWidthFuncT_WithClosures -> C_UnicodeEastasianWidthFuncT
- type C_UnicodeGeneralCategoryFuncT = Ptr UnicodeFuncsT -> Word32 -> Ptr () -> IO CUInt
- type UnicodeGeneralCategoryFuncT = UnicodeFuncsT -> Word32 -> IO UnicodeGeneralCategoryT
- type UnicodeGeneralCategoryFuncT_WithClosures = UnicodeFuncsT -> Word32 -> Ptr () -> IO UnicodeGeneralCategoryT
- drop_closures_UnicodeGeneralCategoryFuncT :: UnicodeGeneralCategoryFuncT -> UnicodeGeneralCategoryFuncT_WithClosures
- dynamic_UnicodeGeneralCategoryFuncT :: (HasCallStack, MonadIO m) => FunPtr C_UnicodeGeneralCategoryFuncT -> UnicodeFuncsT -> Word32 -> Ptr () -> m UnicodeGeneralCategoryT
- genClosure_UnicodeGeneralCategoryFuncT :: MonadIO m => UnicodeGeneralCategoryFuncT -> m (GClosure C_UnicodeGeneralCategoryFuncT)
- mk_UnicodeGeneralCategoryFuncT :: C_UnicodeGeneralCategoryFuncT -> IO (FunPtr C_UnicodeGeneralCategoryFuncT)
- noUnicodeGeneralCategoryFuncT :: Maybe UnicodeGeneralCategoryFuncT
- noUnicodeGeneralCategoryFuncT_WithClosures :: Maybe UnicodeGeneralCategoryFuncT_WithClosures
- wrap_UnicodeGeneralCategoryFuncT :: Maybe (Ptr (FunPtr C_UnicodeGeneralCategoryFuncT)) -> UnicodeGeneralCategoryFuncT_WithClosures -> C_UnicodeGeneralCategoryFuncT
- type C_UnicodeMirroringFuncT = Ptr UnicodeFuncsT -> Word32 -> Ptr () -> IO Word32
- type UnicodeMirroringFuncT = UnicodeFuncsT -> Word32 -> IO Word32
- type UnicodeMirroringFuncT_WithClosures = UnicodeFuncsT -> Word32 -> Ptr () -> IO Word32
- drop_closures_UnicodeMirroringFuncT :: UnicodeMirroringFuncT -> UnicodeMirroringFuncT_WithClosures
- dynamic_UnicodeMirroringFuncT :: (HasCallStack, MonadIO m) => FunPtr C_UnicodeMirroringFuncT -> UnicodeFuncsT -> Word32 -> Ptr () -> m Word32
- genClosure_UnicodeMirroringFuncT :: MonadIO m => UnicodeMirroringFuncT -> m (GClosure C_UnicodeMirroringFuncT)
- mk_UnicodeMirroringFuncT :: C_UnicodeMirroringFuncT -> IO (FunPtr C_UnicodeMirroringFuncT)
- noUnicodeMirroringFuncT :: Maybe UnicodeMirroringFuncT
- noUnicodeMirroringFuncT_WithClosures :: Maybe UnicodeMirroringFuncT_WithClosures
- wrap_UnicodeMirroringFuncT :: Maybe (Ptr (FunPtr C_UnicodeMirroringFuncT)) -> UnicodeMirroringFuncT_WithClosures -> C_UnicodeMirroringFuncT
- type C_UnicodeScriptFuncT = Ptr UnicodeFuncsT -> Word32 -> Ptr () -> IO CUInt
- type UnicodeScriptFuncT = UnicodeFuncsT -> Word32 -> IO ScriptT
- type UnicodeScriptFuncT_WithClosures = UnicodeFuncsT -> Word32 -> Ptr () -> IO ScriptT
- drop_closures_UnicodeScriptFuncT :: UnicodeScriptFuncT -> UnicodeScriptFuncT_WithClosures
- dynamic_UnicodeScriptFuncT :: (HasCallStack, MonadIO m) => FunPtr C_UnicodeScriptFuncT -> UnicodeFuncsT -> Word32 -> Ptr () -> m ScriptT
- genClosure_UnicodeScriptFuncT :: MonadIO m => UnicodeScriptFuncT -> m (GClosure C_UnicodeScriptFuncT)
- mk_UnicodeScriptFuncT :: C_UnicodeScriptFuncT -> IO (FunPtr C_UnicodeScriptFuncT)
- noUnicodeScriptFuncT :: Maybe UnicodeScriptFuncT
- noUnicodeScriptFuncT_WithClosures :: Maybe UnicodeScriptFuncT_WithClosures
- wrap_UnicodeScriptFuncT :: Maybe (Ptr (FunPtr C_UnicodeScriptFuncT)) -> UnicodeScriptFuncT_WithClosures -> C_UnicodeScriptFuncT
Signals
BufferMessageFuncT
type BufferMessageFuncT Source #
type C_BufferMessageFuncT = Ptr BufferT -> Ptr FontT -> CString -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BufferMessageFuncT :: BufferMessageFuncT -> BufferMessageFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BufferMessageFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_BufferMessageFuncT | |
-> BufferT |
|
-> FontT |
|
-> Text |
|
-> Ptr () |
|
-> m Int32 | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_BufferMessageFuncT :: MonadIO m => BufferMessageFuncT -> m (GClosure C_BufferMessageFuncT) Source #
Wrap the callback into a GClosure
.
mk_BufferMessageFuncT :: C_BufferMessageFuncT -> IO (FunPtr C_BufferMessageFuncT) Source #
Generate a function pointer callable from C code, from a C_BufferMessageFuncT
.
noBufferMessageFuncT :: Maybe BufferMessageFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
BufferMessageFuncT
noBufferMessageFuncT_WithClosures :: Maybe BufferMessageFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BufferMessageFuncT_WithClosures
wrap_BufferMessageFuncT :: Maybe (Ptr (FunPtr C_BufferMessageFuncT)) -> BufferMessageFuncT_WithClosures -> C_BufferMessageFuncT Source #
Wrap a BufferMessageFuncT
into a C_BufferMessageFuncT
.
DestroyFuncT
type C_DestroyFuncT = Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type DestroyFuncT = IO () Source #
A virtual method for destroy user-data callbacks.
type DestroyFuncT_WithClosures Source #
A virtual method for destroy user-data callbacks.
drop_closures_DestroyFuncT :: DestroyFuncT -> DestroyFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_DestroyFuncT | |
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DestroyFuncT :: MonadIO m => DestroyFuncT -> m (GClosure C_DestroyFuncT) Source #
Wrap the callback into a GClosure
.
mk_DestroyFuncT :: C_DestroyFuncT -> IO (FunPtr C_DestroyFuncT) Source #
Generate a function pointer callable from C code, from a C_DestroyFuncT
.
noDestroyFuncT :: Maybe DestroyFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
DestroyFuncT
noDestroyFuncT_WithClosures :: Maybe DestroyFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
DestroyFuncT_WithClosures
wrap_DestroyFuncT :: Maybe (Ptr (FunPtr C_DestroyFuncT)) -> DestroyFuncT_WithClosures -> C_DestroyFuncT Source #
Wrap a DestroyFuncT
into a C_DestroyFuncT
.
FontGetGlyphAdvanceFuncT
type C_FontGetGlyphAdvanceFuncT = Ptr FontT -> Ptr () -> Word32 -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type FontGetGlyphAdvanceFuncT Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> IO Int32 | Returns: The advance of |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the advance for a specified glyph. The
method must return an hb_position_t
.
type FontGetGlyphAdvanceFuncT_WithClosures Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Ptr () |
|
-> IO Int32 | Returns: The advance of |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the advance for a specified glyph. The
method must return an hb_position_t
.
drop_closures_FontGetGlyphAdvanceFuncT :: FontGetGlyphAdvanceFuncT -> FontGetGlyphAdvanceFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FontGetGlyphAdvanceFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FontGetGlyphAdvanceFuncT | |
-> FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Ptr () |
|
-> m Int32 | Returns: The advance of |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FontGetGlyphAdvanceFuncT :: MonadIO m => FontGetGlyphAdvanceFuncT -> m (GClosure C_FontGetGlyphAdvanceFuncT) Source #
Wrap the callback into a GClosure
.
mk_FontGetGlyphAdvanceFuncT :: C_FontGetGlyphAdvanceFuncT -> IO (FunPtr C_FontGetGlyphAdvanceFuncT) Source #
Generate a function pointer callable from C code, from a C_FontGetGlyphAdvanceFuncT
.
noFontGetGlyphAdvanceFuncT :: Maybe FontGetGlyphAdvanceFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphAdvanceFuncT
noFontGetGlyphAdvanceFuncT_WithClosures :: Maybe FontGetGlyphAdvanceFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphAdvanceFuncT_WithClosures
wrap_FontGetGlyphAdvanceFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphAdvanceFuncT)) -> FontGetGlyphAdvanceFuncT_WithClosures -> C_FontGetGlyphAdvanceFuncT Source #
Wrap a FontGetGlyphAdvanceFuncT
into a C_FontGetGlyphAdvanceFuncT
.
FontGetGlyphAdvancesFuncT
type C_FontGetGlyphAdvancesFuncT = Ptr FontT -> Ptr () -> Word32 -> Word32 -> Word32 -> Ptr Int32 -> Word32 -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type FontGetGlyphAdvancesFuncT Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> Word32 |
|
-> Word32 |
|
-> IO Int32 |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the advances for a sequence of glyphs.
type FontGetGlyphAdvancesFuncT_WithClosures Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> IO Int32 |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the advances for a sequence of glyphs.
drop_closures_FontGetGlyphAdvancesFuncT :: FontGetGlyphAdvancesFuncT -> FontGetGlyphAdvancesFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FontGetGlyphAdvancesFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FontGetGlyphAdvancesFuncT | |
-> FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> m Int32 |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FontGetGlyphAdvancesFuncT :: MonadIO m => FontGetGlyphAdvancesFuncT -> m (GClosure C_FontGetGlyphAdvancesFuncT) Source #
Wrap the callback into a GClosure
.
mk_FontGetGlyphAdvancesFuncT :: C_FontGetGlyphAdvancesFuncT -> IO (FunPtr C_FontGetGlyphAdvancesFuncT) Source #
Generate a function pointer callable from C code, from a C_FontGetGlyphAdvancesFuncT
.
noFontGetGlyphAdvancesFuncT :: Maybe FontGetGlyphAdvancesFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphAdvancesFuncT
noFontGetGlyphAdvancesFuncT_WithClosures :: Maybe FontGetGlyphAdvancesFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphAdvancesFuncT_WithClosures
wrap_FontGetGlyphAdvancesFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphAdvancesFuncT)) -> FontGetGlyphAdvancesFuncT_WithClosures -> C_FontGetGlyphAdvancesFuncT Source #
Wrap a FontGetGlyphAdvancesFuncT
into a C_FontGetGlyphAdvancesFuncT
.
FontGetGlyphContourPointFuncT
type C_FontGetGlyphContourPointFuncT = Ptr FontT -> Ptr () -> Word32 -> Word32 -> Ptr Int32 -> Ptr Int32 -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type FontGetGlyphContourPointFuncT Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> IO (Int32, Int32, Int32) | Returns: |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the (X,Y) coordinates (in font units) for a
specified contour point in a glyph. Each coordinate must be returned as
an hb_position_t
output parameter.
type FontGetGlyphContourPointFuncT_WithClosures Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> IO (Int32, Int32, Int32) | Returns: |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the (X,Y) coordinates (in font units) for a
specified contour point in a glyph. Each coordinate must be returned as
an hb_position_t
output parameter.
drop_closures_FontGetGlyphContourPointFuncT :: FontGetGlyphContourPointFuncT -> FontGetGlyphContourPointFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FontGetGlyphContourPointFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FontGetGlyphContourPointFuncT | |
-> FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> m (Int32, Int32, Int32) | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FontGetGlyphContourPointFuncT :: MonadIO m => FontGetGlyphContourPointFuncT -> m (GClosure C_FontGetGlyphContourPointFuncT) Source #
Wrap the callback into a GClosure
.
mk_FontGetGlyphContourPointFuncT :: C_FontGetGlyphContourPointFuncT -> IO (FunPtr C_FontGetGlyphContourPointFuncT) Source #
Generate a function pointer callable from C code, from a C_FontGetGlyphContourPointFuncT
.
noFontGetGlyphContourPointFuncT :: Maybe FontGetGlyphContourPointFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphContourPointFuncT
noFontGetGlyphContourPointFuncT_WithClosures :: Maybe FontGetGlyphContourPointFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphContourPointFuncT_WithClosures
wrap_FontGetGlyphContourPointFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphContourPointFuncT)) -> FontGetGlyphContourPointFuncT_WithClosures -> C_FontGetGlyphContourPointFuncT Source #
Wrap a FontGetGlyphContourPointFuncT
into a C_FontGetGlyphContourPointFuncT
.
FontGetGlyphFromNameFuncT
type C_FontGetGlyphFromNameFuncT = Ptr FontT -> Ptr () -> Ptr CString -> Int32 -> Ptr Word32 -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type FontGetGlyphFromNameFuncT Source #
= FontT |
|
-> Ptr () |
|
-> [Text] |
|
-> IO (Int32, Word32) | Returns: |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the glyph ID that corresponds to a glyph-name string.
type FontGetGlyphFromNameFuncT_WithClosures Source #
= FontT |
|
-> Ptr () |
|
-> [Text] |
|
-> Ptr () |
|
-> IO (Int32, Word32) | Returns: |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the glyph ID that corresponds to a glyph-name string.
drop_closures_FontGetGlyphFromNameFuncT :: FontGetGlyphFromNameFuncT -> FontGetGlyphFromNameFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FontGetGlyphFromNameFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FontGetGlyphFromNameFuncT | |
-> FontT |
|
-> Ptr () |
|
-> [Text] |
|
-> Ptr () |
|
-> m (Int32, Word32) | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FontGetGlyphFromNameFuncT :: MonadIO m => FontGetGlyphFromNameFuncT -> m (GClosure C_FontGetGlyphFromNameFuncT) Source #
Wrap the callback into a GClosure
.
mk_FontGetGlyphFromNameFuncT :: C_FontGetGlyphFromNameFuncT -> IO (FunPtr C_FontGetGlyphFromNameFuncT) Source #
Generate a function pointer callable from C code, from a C_FontGetGlyphFromNameFuncT
.
noFontGetGlyphFromNameFuncT :: Maybe FontGetGlyphFromNameFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphFromNameFuncT
noFontGetGlyphFromNameFuncT_WithClosures :: Maybe FontGetGlyphFromNameFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphFromNameFuncT_WithClosures
wrap_FontGetGlyphFromNameFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphFromNameFuncT)) -> FontGetGlyphFromNameFuncT_WithClosures -> C_FontGetGlyphFromNameFuncT Source #
Wrap a FontGetGlyphFromNameFuncT
into a C_FontGetGlyphFromNameFuncT
.
FontGetGlyphFuncT
type C_FontGetGlyphFuncT = Ptr FontT -> Ptr () -> Word32 -> Word32 -> Ptr Word32 -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type FontGetGlyphFuncT Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> IO (Int32, Word32) | Returns: |
Deprecated: (Since version 1.2.3)
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the glyph ID for a specified Unicode code point font, with an optional variation selector.
type FontGetGlyphFuncT_WithClosures Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> IO (Int32, Word32) | Returns: |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the glyph ID for a specified Unicode code point font, with an optional variation selector.
drop_closures_FontGetGlyphFuncT :: FontGetGlyphFuncT -> FontGetGlyphFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FontGetGlyphFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FontGetGlyphFuncT | |
-> FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> m (Int32, Word32) | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FontGetGlyphFuncT :: MonadIO m => FontGetGlyphFuncT -> m (GClosure C_FontGetGlyphFuncT) Source #
Wrap the callback into a GClosure
.
mk_FontGetGlyphFuncT :: C_FontGetGlyphFuncT -> IO (FunPtr C_FontGetGlyphFuncT) Source #
Generate a function pointer callable from C code, from a C_FontGetGlyphFuncT
.
noFontGetGlyphFuncT :: Maybe FontGetGlyphFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphFuncT
noFontGetGlyphFuncT_WithClosures :: Maybe FontGetGlyphFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphFuncT_WithClosures
wrap_FontGetGlyphFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphFuncT)) -> FontGetGlyphFuncT_WithClosures -> C_FontGetGlyphFuncT Source #
Wrap a FontGetGlyphFuncT
into a C_FontGetGlyphFuncT
.
FontGetGlyphKerningFuncT
type C_FontGetGlyphKerningFuncT = Ptr FontT -> Ptr () -> Word32 -> Word32 -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type FontGetGlyphKerningFuncT Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> IO Int32 |
This method should retrieve the kerning-adjustment value for a glyph-pair in the specified font, for horizontal text segments.
type FontGetGlyphKerningFuncT_WithClosures Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> IO Int32 |
This method should retrieve the kerning-adjustment value for a glyph-pair in the specified font, for horizontal text segments.
drop_closures_FontGetGlyphKerningFuncT :: FontGetGlyphKerningFuncT -> FontGetGlyphKerningFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FontGetGlyphKerningFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FontGetGlyphKerningFuncT | |
-> FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> m Int32 |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FontGetGlyphKerningFuncT :: MonadIO m => FontGetGlyphKerningFuncT -> m (GClosure C_FontGetGlyphKerningFuncT) Source #
Wrap the callback into a GClosure
.
mk_FontGetGlyphKerningFuncT :: C_FontGetGlyphKerningFuncT -> IO (FunPtr C_FontGetGlyphKerningFuncT) Source #
Generate a function pointer callable from C code, from a C_FontGetGlyphKerningFuncT
.
noFontGetGlyphKerningFuncT :: Maybe FontGetGlyphKerningFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphKerningFuncT
noFontGetGlyphKerningFuncT_WithClosures :: Maybe FontGetGlyphKerningFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphKerningFuncT_WithClosures
wrap_FontGetGlyphKerningFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphKerningFuncT)) -> FontGetGlyphKerningFuncT_WithClosures -> C_FontGetGlyphKerningFuncT Source #
Wrap a FontGetGlyphKerningFuncT
into a C_FontGetGlyphKerningFuncT
.
FontGetGlyphNameFuncT
type C_FontGetGlyphNameFuncT = Ptr FontT -> Ptr () -> Word32 -> Ptr (Ptr CString) -> Ptr Word32 -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type FontGetGlyphNameFuncT Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> IO (Int32, [Text]) | Returns: |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the glyph name that corresponds to a glyph ID. The name should be returned in a string output parameter.
type FontGetGlyphNameFuncT_WithClosures Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Ptr () |
|
-> IO (Int32, [Text]) | Returns: |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the glyph name that corresponds to a glyph ID. The name should be returned in a string output parameter.
drop_closures_FontGetGlyphNameFuncT :: FontGetGlyphNameFuncT -> FontGetGlyphNameFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FontGetGlyphNameFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FontGetGlyphNameFuncT | |
-> FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Ptr () |
|
-> m (Int32, [Text]) | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FontGetGlyphNameFuncT :: MonadIO m => FontGetGlyphNameFuncT -> m (GClosure C_FontGetGlyphNameFuncT) Source #
Wrap the callback into a GClosure
.
mk_FontGetGlyphNameFuncT :: C_FontGetGlyphNameFuncT -> IO (FunPtr C_FontGetGlyphNameFuncT) Source #
Generate a function pointer callable from C code, from a C_FontGetGlyphNameFuncT
.
noFontGetGlyphNameFuncT :: Maybe FontGetGlyphNameFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphNameFuncT
noFontGetGlyphNameFuncT_WithClosures :: Maybe FontGetGlyphNameFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphNameFuncT_WithClosures
wrap_FontGetGlyphNameFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphNameFuncT)) -> FontGetGlyphNameFuncT_WithClosures -> C_FontGetGlyphNameFuncT Source #
Wrap a FontGetGlyphNameFuncT
into a C_FontGetGlyphNameFuncT
.
FontGetGlyphOriginFuncT
type C_FontGetGlyphOriginFuncT = Ptr FontT -> Ptr () -> Word32 -> Ptr Int32 -> Ptr Int32 -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type FontGetGlyphOriginFuncT Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> IO (Int32, Int32, Int32) | Returns: |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the (X,Y) coordinates (in font units) of the
origin for a glyph. Each coordinate must be returned in an hb_position_t
output parameter.
type FontGetGlyphOriginFuncT_WithClosures Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Ptr () |
|
-> IO (Int32, Int32, Int32) | Returns: |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the (X,Y) coordinates (in font units) of the
origin for a glyph. Each coordinate must be returned in an hb_position_t
output parameter.
drop_closures_FontGetGlyphOriginFuncT :: FontGetGlyphOriginFuncT -> FontGetGlyphOriginFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FontGetGlyphOriginFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FontGetGlyphOriginFuncT | |
-> FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Ptr () |
|
-> m (Int32, Int32, Int32) | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FontGetGlyphOriginFuncT :: MonadIO m => FontGetGlyphOriginFuncT -> m (GClosure C_FontGetGlyphOriginFuncT) Source #
Wrap the callback into a GClosure
.
mk_FontGetGlyphOriginFuncT :: C_FontGetGlyphOriginFuncT -> IO (FunPtr C_FontGetGlyphOriginFuncT) Source #
Generate a function pointer callable from C code, from a C_FontGetGlyphOriginFuncT
.
noFontGetGlyphOriginFuncT :: Maybe FontGetGlyphOriginFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphOriginFuncT
noFontGetGlyphOriginFuncT_WithClosures :: Maybe FontGetGlyphOriginFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetGlyphOriginFuncT_WithClosures
wrap_FontGetGlyphOriginFuncT :: Maybe (Ptr (FunPtr C_FontGetGlyphOriginFuncT)) -> FontGetGlyphOriginFuncT_WithClosures -> C_FontGetGlyphOriginFuncT Source #
Wrap a FontGetGlyphOriginFuncT
into a C_FontGetGlyphOriginFuncT
.
FontGetNominalGlyphFuncT
type C_FontGetNominalGlyphFuncT = Ptr FontT -> Ptr () -> Word32 -> Ptr Word32 -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type FontGetNominalGlyphFuncT Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> IO (Int32, Word32) | Returns: |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the nominal glyph ID for a specified Unicode code
point. Glyph IDs must be returned in a hb_codepoint_t
output parameter.
type FontGetNominalGlyphFuncT_WithClosures Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Ptr () |
|
-> IO (Int32, Word32) | Returns: |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the nominal glyph ID for a specified Unicode code
point. Glyph IDs must be returned in a hb_codepoint_t
output parameter.
drop_closures_FontGetNominalGlyphFuncT :: FontGetNominalGlyphFuncT -> FontGetNominalGlyphFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FontGetNominalGlyphFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FontGetNominalGlyphFuncT | |
-> FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Ptr () |
|
-> m (Int32, Word32) | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FontGetNominalGlyphFuncT :: MonadIO m => FontGetNominalGlyphFuncT -> m (GClosure C_FontGetNominalGlyphFuncT) Source #
Wrap the callback into a GClosure
.
mk_FontGetNominalGlyphFuncT :: C_FontGetNominalGlyphFuncT -> IO (FunPtr C_FontGetNominalGlyphFuncT) Source #
Generate a function pointer callable from C code, from a C_FontGetNominalGlyphFuncT
.
noFontGetNominalGlyphFuncT :: Maybe FontGetNominalGlyphFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetNominalGlyphFuncT
noFontGetNominalGlyphFuncT_WithClosures :: Maybe FontGetNominalGlyphFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetNominalGlyphFuncT_WithClosures
wrap_FontGetNominalGlyphFuncT :: Maybe (Ptr (FunPtr C_FontGetNominalGlyphFuncT)) -> FontGetNominalGlyphFuncT_WithClosures -> C_FontGetNominalGlyphFuncT Source #
Wrap a FontGetNominalGlyphFuncT
into a C_FontGetNominalGlyphFuncT
.
FontGetNominalGlyphsFuncT
type C_FontGetNominalGlyphsFuncT = Ptr FontT -> Ptr () -> Word32 -> Word32 -> Word32 -> Ptr Word32 -> Word32 -> Ptr () -> IO Word32 Source #
Type for the callback on the (unwrapped) C side.
type FontGetNominalGlyphsFuncT Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> Word32 |
|
-> Word32 |
|
-> IO (Word32, Word32) | Returns: the number of code points processed |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the nominal glyph IDs for a sequence of
Unicode code points. Glyph IDs must be returned in a hb_codepoint_t
output parameter.
type FontGetNominalGlyphsFuncT_WithClosures Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> IO (Word32, Word32) | Returns: the number of code points processed |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the nominal glyph IDs for a sequence of
Unicode code points. Glyph IDs must be returned in a hb_codepoint_t
output parameter.
drop_closures_FontGetNominalGlyphsFuncT :: FontGetNominalGlyphsFuncT -> FontGetNominalGlyphsFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FontGetNominalGlyphsFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FontGetNominalGlyphsFuncT | |
-> FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> m (Word32, Word32) | Returns: the number of code points processed |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FontGetNominalGlyphsFuncT :: MonadIO m => FontGetNominalGlyphsFuncT -> m (GClosure C_FontGetNominalGlyphsFuncT) Source #
Wrap the callback into a GClosure
.
mk_FontGetNominalGlyphsFuncT :: C_FontGetNominalGlyphsFuncT -> IO (FunPtr C_FontGetNominalGlyphsFuncT) Source #
Generate a function pointer callable from C code, from a C_FontGetNominalGlyphsFuncT
.
noFontGetNominalGlyphsFuncT :: Maybe FontGetNominalGlyphsFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetNominalGlyphsFuncT
noFontGetNominalGlyphsFuncT_WithClosures :: Maybe FontGetNominalGlyphsFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetNominalGlyphsFuncT_WithClosures
wrap_FontGetNominalGlyphsFuncT :: Maybe (Ptr (FunPtr C_FontGetNominalGlyphsFuncT)) -> FontGetNominalGlyphsFuncT_WithClosures -> C_FontGetNominalGlyphsFuncT Source #
Wrap a FontGetNominalGlyphsFuncT
into a C_FontGetNominalGlyphsFuncT
.
FontGetVariationGlyphFuncT
type C_FontGetVariationGlyphFuncT = Ptr FontT -> Ptr () -> Word32 -> Word32 -> Ptr Word32 -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type FontGetVariationGlyphFuncT Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> IO (Int32, Word32) | Returns: |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the glyph ID for a specified Unicode code point
followed by a specified Variation Selector code point. Glyph IDs must be
returned in a hb_codepoint_t
output parameter.
type FontGetVariationGlyphFuncT_WithClosures Source #
= FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> IO (Int32, Word32) | Returns: |
A virtual method for the FontFuncsT
of an FontT
object.
This method should retrieve the glyph ID for a specified Unicode code point
followed by a specified Variation Selector code point. Glyph IDs must be
returned in a hb_codepoint_t
output parameter.
drop_closures_FontGetVariationGlyphFuncT :: FontGetVariationGlyphFuncT -> FontGetVariationGlyphFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FontGetVariationGlyphFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FontGetVariationGlyphFuncT | |
-> FontT |
|
-> Ptr () |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> m (Int32, Word32) | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FontGetVariationGlyphFuncT :: MonadIO m => FontGetVariationGlyphFuncT -> m (GClosure C_FontGetVariationGlyphFuncT) Source #
Wrap the callback into a GClosure
.
mk_FontGetVariationGlyphFuncT :: C_FontGetVariationGlyphFuncT -> IO (FunPtr C_FontGetVariationGlyphFuncT) Source #
Generate a function pointer callable from C code, from a C_FontGetVariationGlyphFuncT
.
noFontGetVariationGlyphFuncT :: Maybe FontGetVariationGlyphFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetVariationGlyphFuncT
noFontGetVariationGlyphFuncT_WithClosures :: Maybe FontGetVariationGlyphFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FontGetVariationGlyphFuncT_WithClosures
wrap_FontGetVariationGlyphFuncT :: Maybe (Ptr (FunPtr C_FontGetVariationGlyphFuncT)) -> FontGetVariationGlyphFuncT_WithClosures -> C_FontGetVariationGlyphFuncT Source #
Wrap a FontGetVariationGlyphFuncT
into a C_FontGetVariationGlyphFuncT
.
ReferenceTableFuncT
type C_ReferenceTableFuncT = Ptr FaceT -> Word32 -> Ptr () -> IO (Ptr BlobT) Source #
Type for the callback on the (unwrapped) C side.
type ReferenceTableFuncT Source #
= FaceT |
|
-> Word32 |
|
-> IO BlobT | Returns: A pointer to the |
Callback function for faceCreateForTables
.
Since: 0.9.2
type ReferenceTableFuncT_WithClosures Source #
= FaceT |
|
-> Word32 |
|
-> Ptr () |
|
-> IO BlobT | Returns: A pointer to the |
Callback function for faceCreateForTables
.
Since: 0.9.2
drop_closures_ReferenceTableFuncT :: ReferenceTableFuncT -> ReferenceTableFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ReferenceTableFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_ReferenceTableFuncT | |
-> FaceT |
|
-> Word32 |
|
-> Ptr () |
|
-> m BlobT | Returns: A pointer to the |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ReferenceTableFuncT :: MonadIO m => ReferenceTableFuncT -> m (GClosure C_ReferenceTableFuncT) Source #
Wrap the callback into a GClosure
.
mk_ReferenceTableFuncT :: C_ReferenceTableFuncT -> IO (FunPtr C_ReferenceTableFuncT) Source #
Generate a function pointer callable from C code, from a C_ReferenceTableFuncT
.
noReferenceTableFuncT :: Maybe ReferenceTableFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
ReferenceTableFuncT
noReferenceTableFuncT_WithClosures :: Maybe ReferenceTableFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ReferenceTableFuncT_WithClosures
wrap_ReferenceTableFuncT :: Maybe (Ptr (FunPtr C_ReferenceTableFuncT)) -> ReferenceTableFuncT_WithClosures -> C_ReferenceTableFuncT Source #
Wrap a ReferenceTableFuncT
into a C_ReferenceTableFuncT
.
UnicodeCombiningClassFuncT
type C_UnicodeCombiningClassFuncT = Ptr UnicodeFuncsT -> Word32 -> Ptr () -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type UnicodeCombiningClassFuncT Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> IO UnicodeCombiningClassT | Returns: The |
A virtual method for the UnicodeFuncsT
structure.
This method should retrieve the Canonical Combining Class (ccc) property for a specified Unicode code point.
type UnicodeCombiningClassFuncT_WithClosures Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> Ptr () |
|
-> IO UnicodeCombiningClassT | Returns: The |
A virtual method for the UnicodeFuncsT
structure.
This method should retrieve the Canonical Combining Class (ccc) property for a specified Unicode code point.
drop_closures_UnicodeCombiningClassFuncT :: UnicodeCombiningClassFuncT -> UnicodeCombiningClassFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_UnicodeCombiningClassFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_UnicodeCombiningClassFuncT | |
-> UnicodeFuncsT |
|
-> Word32 |
|
-> Ptr () |
|
-> m UnicodeCombiningClassT | Returns: The |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_UnicodeCombiningClassFuncT :: MonadIO m => UnicodeCombiningClassFuncT -> m (GClosure C_UnicodeCombiningClassFuncT) Source #
Wrap the callback into a GClosure
.
mk_UnicodeCombiningClassFuncT :: C_UnicodeCombiningClassFuncT -> IO (FunPtr C_UnicodeCombiningClassFuncT) Source #
Generate a function pointer callable from C code, from a C_UnicodeCombiningClassFuncT
.
noUnicodeCombiningClassFuncT :: Maybe UnicodeCombiningClassFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeCombiningClassFuncT
noUnicodeCombiningClassFuncT_WithClosures :: Maybe UnicodeCombiningClassFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeCombiningClassFuncT_WithClosures
wrap_UnicodeCombiningClassFuncT :: Maybe (Ptr (FunPtr C_UnicodeCombiningClassFuncT)) -> UnicodeCombiningClassFuncT_WithClosures -> C_UnicodeCombiningClassFuncT Source #
Wrap a UnicodeCombiningClassFuncT
into a C_UnicodeCombiningClassFuncT
.
UnicodeComposeFuncT
type C_UnicodeComposeFuncT = Ptr UnicodeFuncsT -> Word32 -> Word32 -> Ptr Word32 -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type UnicodeComposeFuncT Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> Word32 |
|
-> IO (Int32, Word32) | Returns: |
A virtual method for the UnicodeFuncsT
structure.
This method should compose a sequence of two input Unicode code
points by canonical equivalence, returning the composed code
point in a hb_codepoint_t
output parameter (if successful).
The method must return an hb_bool_t
indicating the success
of the composition.
type UnicodeComposeFuncT_WithClosures Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> IO (Int32, Word32) | Returns: |
A virtual method for the UnicodeFuncsT
structure.
This method should compose a sequence of two input Unicode code
points by canonical equivalence, returning the composed code
point in a hb_codepoint_t
output parameter (if successful).
The method must return an hb_bool_t
indicating the success
of the composition.
drop_closures_UnicodeComposeFuncT :: UnicodeComposeFuncT -> UnicodeComposeFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_UnicodeComposeFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_UnicodeComposeFuncT | |
-> UnicodeFuncsT |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> m (Int32, Word32) | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_UnicodeComposeFuncT :: MonadIO m => UnicodeComposeFuncT -> m (GClosure C_UnicodeComposeFuncT) Source #
Wrap the callback into a GClosure
.
mk_UnicodeComposeFuncT :: C_UnicodeComposeFuncT -> IO (FunPtr C_UnicodeComposeFuncT) Source #
Generate a function pointer callable from C code, from a C_UnicodeComposeFuncT
.
noUnicodeComposeFuncT :: Maybe UnicodeComposeFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeComposeFuncT
noUnicodeComposeFuncT_WithClosures :: Maybe UnicodeComposeFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeComposeFuncT_WithClosures
wrap_UnicodeComposeFuncT :: Maybe (Ptr (FunPtr C_UnicodeComposeFuncT)) -> UnicodeComposeFuncT_WithClosures -> C_UnicodeComposeFuncT Source #
Wrap a UnicodeComposeFuncT
into a C_UnicodeComposeFuncT
.
UnicodeDecomposeCompatibilityFuncT
type C_UnicodeDecomposeCompatibilityFuncT = Ptr UnicodeFuncsT -> Word32 -> Word32 -> Ptr () -> IO Word32 Source #
Type for the callback on the (unwrapped) C side.
type UnicodeDecomposeCompatibilityFuncT Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> Word32 |
|
-> IO Word32 | Returns: number of codepoints in the full compatibility decomposition of |
Deprecated: (Since version 2.0.0)
Fully decompose u
to its Unicode compatibility decomposition. The codepoints of the decomposition will be written to decomposed
.
The complete length of the decomposition will be returned.
If u
has no compatibility decomposition, zero should be returned.
The Unicode standard guarantees that a buffer of length UNICODE_MAX_DECOMPOSITION_LEN
codepoints will always be sufficient for any
compatibility decomposition plus an terminating value of 0. Consequently, decompose
must be allocated by the caller to be at least this length. Implementations
of this function type must ensure that they do not write past the provided array.
type UnicodeDecomposeCompatibilityFuncT_WithClosures Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> IO Word32 | Returns: number of codepoints in the full compatibility decomposition of |
Fully decompose u
to its Unicode compatibility decomposition. The codepoints of the decomposition will be written to decomposed
.
The complete length of the decomposition will be returned.
If u
has no compatibility decomposition, zero should be returned.
The Unicode standard guarantees that a buffer of length UNICODE_MAX_DECOMPOSITION_LEN
codepoints will always be sufficient for any
compatibility decomposition plus an terminating value of 0. Consequently, decompose
must be allocated by the caller to be at least this length. Implementations
of this function type must ensure that they do not write past the provided array.
drop_closures_UnicodeDecomposeCompatibilityFuncT :: UnicodeDecomposeCompatibilityFuncT -> UnicodeDecomposeCompatibilityFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_UnicodeDecomposeCompatibilityFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_UnicodeDecomposeCompatibilityFuncT | |
-> UnicodeFuncsT |
|
-> Word32 |
|
-> Word32 |
|
-> Ptr () |
|
-> m Word32 | Returns: number of codepoints in the full compatibility decomposition of |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_UnicodeDecomposeCompatibilityFuncT :: MonadIO m => UnicodeDecomposeCompatibilityFuncT -> m (GClosure C_UnicodeDecomposeCompatibilityFuncT) Source #
Wrap the callback into a GClosure
.
mk_UnicodeDecomposeCompatibilityFuncT :: C_UnicodeDecomposeCompatibilityFuncT -> IO (FunPtr C_UnicodeDecomposeCompatibilityFuncT) Source #
Generate a function pointer callable from C code, from a C_UnicodeDecomposeCompatibilityFuncT
.
noUnicodeDecomposeCompatibilityFuncT :: Maybe UnicodeDecomposeCompatibilityFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeDecomposeCompatibilityFuncT
noUnicodeDecomposeCompatibilityFuncT_WithClosures :: Maybe UnicodeDecomposeCompatibilityFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeDecomposeCompatibilityFuncT_WithClosures
wrap_UnicodeDecomposeCompatibilityFuncT :: Maybe (Ptr (FunPtr C_UnicodeDecomposeCompatibilityFuncT)) -> UnicodeDecomposeCompatibilityFuncT_WithClosures -> C_UnicodeDecomposeCompatibilityFuncT Source #
UnicodeDecomposeFuncT
type C_UnicodeDecomposeFuncT = Ptr UnicodeFuncsT -> Word32 -> Ptr Word32 -> Ptr Word32 -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type UnicodeDecomposeFuncT Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> IO (Int32, Word32, Word32) | Returns: |
A virtual method for the UnicodeFuncsT
structure.
This method should decompose an input Unicode code point,
returning the two decomposed code points in hb_codepoint_t
output parameters (if successful). The method must return an
hb_bool_t
indicating the success of the composition.
type UnicodeDecomposeFuncT_WithClosures Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> Ptr () |
|
-> IO (Int32, Word32, Word32) | Returns: |
A virtual method for the UnicodeFuncsT
structure.
This method should decompose an input Unicode code point,
returning the two decomposed code points in hb_codepoint_t
output parameters (if successful). The method must return an
hb_bool_t
indicating the success of the composition.
drop_closures_UnicodeDecomposeFuncT :: UnicodeDecomposeFuncT -> UnicodeDecomposeFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_UnicodeDecomposeFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_UnicodeDecomposeFuncT | |
-> UnicodeFuncsT |
|
-> Word32 |
|
-> Ptr () |
|
-> m (Int32, Word32, Word32) | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_UnicodeDecomposeFuncT :: MonadIO m => UnicodeDecomposeFuncT -> m (GClosure C_UnicodeDecomposeFuncT) Source #
Wrap the callback into a GClosure
.
mk_UnicodeDecomposeFuncT :: C_UnicodeDecomposeFuncT -> IO (FunPtr C_UnicodeDecomposeFuncT) Source #
Generate a function pointer callable from C code, from a C_UnicodeDecomposeFuncT
.
noUnicodeDecomposeFuncT :: Maybe UnicodeDecomposeFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeDecomposeFuncT
noUnicodeDecomposeFuncT_WithClosures :: Maybe UnicodeDecomposeFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeDecomposeFuncT_WithClosures
wrap_UnicodeDecomposeFuncT :: Maybe (Ptr (FunPtr C_UnicodeDecomposeFuncT)) -> UnicodeDecomposeFuncT_WithClosures -> C_UnicodeDecomposeFuncT Source #
Wrap a UnicodeDecomposeFuncT
into a C_UnicodeDecomposeFuncT
.
UnicodeEastasianWidthFuncT
type C_UnicodeEastasianWidthFuncT = Ptr UnicodeFuncsT -> Word32 -> Ptr () -> IO Word32 Source #
Type for the callback on the (unwrapped) C side.
type UnicodeEastasianWidthFuncT Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> IO Word32 |
Deprecated: (Since version 2.0.0)
A virtual method for the UnicodeFuncsT
structure.
type UnicodeEastasianWidthFuncT_WithClosures Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> Ptr () |
|
-> IO Word32 |
A virtual method for the UnicodeFuncsT
structure.
drop_closures_UnicodeEastasianWidthFuncT :: UnicodeEastasianWidthFuncT -> UnicodeEastasianWidthFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_UnicodeEastasianWidthFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_UnicodeEastasianWidthFuncT | |
-> UnicodeFuncsT |
|
-> Word32 |
|
-> Ptr () |
|
-> m Word32 |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_UnicodeEastasianWidthFuncT :: MonadIO m => UnicodeEastasianWidthFuncT -> m (GClosure C_UnicodeEastasianWidthFuncT) Source #
Wrap the callback into a GClosure
.
mk_UnicodeEastasianWidthFuncT :: C_UnicodeEastasianWidthFuncT -> IO (FunPtr C_UnicodeEastasianWidthFuncT) Source #
Generate a function pointer callable from C code, from a C_UnicodeEastasianWidthFuncT
.
noUnicodeEastasianWidthFuncT :: Maybe UnicodeEastasianWidthFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeEastasianWidthFuncT
noUnicodeEastasianWidthFuncT_WithClosures :: Maybe UnicodeEastasianWidthFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeEastasianWidthFuncT_WithClosures
wrap_UnicodeEastasianWidthFuncT :: Maybe (Ptr (FunPtr C_UnicodeEastasianWidthFuncT)) -> UnicodeEastasianWidthFuncT_WithClosures -> C_UnicodeEastasianWidthFuncT Source #
Wrap a UnicodeEastasianWidthFuncT
into a C_UnicodeEastasianWidthFuncT
.
UnicodeGeneralCategoryFuncT
type C_UnicodeGeneralCategoryFuncT = Ptr UnicodeFuncsT -> Word32 -> Ptr () -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type UnicodeGeneralCategoryFuncT Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> IO UnicodeGeneralCategoryT | Returns: The |
A virtual method for the UnicodeFuncsT
structure.
This method should retrieve the General Category property for a specified Unicode code point.
type UnicodeGeneralCategoryFuncT_WithClosures Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> Ptr () |
|
-> IO UnicodeGeneralCategoryT | Returns: The |
A virtual method for the UnicodeFuncsT
structure.
This method should retrieve the General Category property for a specified Unicode code point.
drop_closures_UnicodeGeneralCategoryFuncT :: UnicodeGeneralCategoryFuncT -> UnicodeGeneralCategoryFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_UnicodeGeneralCategoryFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_UnicodeGeneralCategoryFuncT | |
-> UnicodeFuncsT |
|
-> Word32 |
|
-> Ptr () |
|
-> m UnicodeGeneralCategoryT | Returns: The |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_UnicodeGeneralCategoryFuncT :: MonadIO m => UnicodeGeneralCategoryFuncT -> m (GClosure C_UnicodeGeneralCategoryFuncT) Source #
Wrap the callback into a GClosure
.
mk_UnicodeGeneralCategoryFuncT :: C_UnicodeGeneralCategoryFuncT -> IO (FunPtr C_UnicodeGeneralCategoryFuncT) Source #
Generate a function pointer callable from C code, from a C_UnicodeGeneralCategoryFuncT
.
noUnicodeGeneralCategoryFuncT :: Maybe UnicodeGeneralCategoryFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeGeneralCategoryFuncT
noUnicodeGeneralCategoryFuncT_WithClosures :: Maybe UnicodeGeneralCategoryFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeGeneralCategoryFuncT_WithClosures
wrap_UnicodeGeneralCategoryFuncT :: Maybe (Ptr (FunPtr C_UnicodeGeneralCategoryFuncT)) -> UnicodeGeneralCategoryFuncT_WithClosures -> C_UnicodeGeneralCategoryFuncT Source #
Wrap a UnicodeGeneralCategoryFuncT
into a C_UnicodeGeneralCategoryFuncT
.
UnicodeMirroringFuncT
type C_UnicodeMirroringFuncT = Ptr UnicodeFuncsT -> Word32 -> Ptr () -> IO Word32 Source #
Type for the callback on the (unwrapped) C side.
type UnicodeMirroringFuncT Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> IO Word32 | Returns: The |
A virtual method for the UnicodeFuncsT
structure.
This method should retrieve the Bi-Directional Mirroring Glyph code point for a specified Unicode code point.
<note>Note: If a code point does not have a specified Bi-Directional Mirroring Glyph defined, the method should return the original code point.</note>
type UnicodeMirroringFuncT_WithClosures Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> Ptr () |
|
-> IO Word32 | Returns: The |
A virtual method for the UnicodeFuncsT
structure.
This method should retrieve the Bi-Directional Mirroring Glyph code point for a specified Unicode code point.
<note>Note: If a code point does not have a specified Bi-Directional Mirroring Glyph defined, the method should return the original code point.</note>
drop_closures_UnicodeMirroringFuncT :: UnicodeMirroringFuncT -> UnicodeMirroringFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_UnicodeMirroringFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_UnicodeMirroringFuncT | |
-> UnicodeFuncsT |
|
-> Word32 |
|
-> Ptr () |
|
-> m Word32 | Returns: The |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_UnicodeMirroringFuncT :: MonadIO m => UnicodeMirroringFuncT -> m (GClosure C_UnicodeMirroringFuncT) Source #
Wrap the callback into a GClosure
.
mk_UnicodeMirroringFuncT :: C_UnicodeMirroringFuncT -> IO (FunPtr C_UnicodeMirroringFuncT) Source #
Generate a function pointer callable from C code, from a C_UnicodeMirroringFuncT
.
noUnicodeMirroringFuncT :: Maybe UnicodeMirroringFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeMirroringFuncT
noUnicodeMirroringFuncT_WithClosures :: Maybe UnicodeMirroringFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeMirroringFuncT_WithClosures
wrap_UnicodeMirroringFuncT :: Maybe (Ptr (FunPtr C_UnicodeMirroringFuncT)) -> UnicodeMirroringFuncT_WithClosures -> C_UnicodeMirroringFuncT Source #
Wrap a UnicodeMirroringFuncT
into a C_UnicodeMirroringFuncT
.
UnicodeScriptFuncT
type C_UnicodeScriptFuncT = Ptr UnicodeFuncsT -> Word32 -> Ptr () -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type UnicodeScriptFuncT Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> IO ScriptT | Returns: The |
A virtual method for the UnicodeFuncsT
structure.
This method should retrieve the Script property for a specified Unicode code point.
type UnicodeScriptFuncT_WithClosures Source #
= UnicodeFuncsT |
|
-> Word32 |
|
-> Ptr () |
|
-> IO ScriptT | Returns: The |
A virtual method for the UnicodeFuncsT
structure.
This method should retrieve the Script property for a specified Unicode code point.
drop_closures_UnicodeScriptFuncT :: UnicodeScriptFuncT -> UnicodeScriptFuncT_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_UnicodeScriptFuncT Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_UnicodeScriptFuncT | |
-> UnicodeFuncsT |
|
-> Word32 |
|
-> Ptr () |
|
-> m ScriptT | Returns: The |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_UnicodeScriptFuncT :: MonadIO m => UnicodeScriptFuncT -> m (GClosure C_UnicodeScriptFuncT) Source #
Wrap the callback into a GClosure
.
mk_UnicodeScriptFuncT :: C_UnicodeScriptFuncT -> IO (FunPtr C_UnicodeScriptFuncT) Source #
Generate a function pointer callable from C code, from a C_UnicodeScriptFuncT
.
noUnicodeScriptFuncT :: Maybe UnicodeScriptFuncT Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeScriptFuncT
noUnicodeScriptFuncT_WithClosures :: Maybe UnicodeScriptFuncT_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
UnicodeScriptFuncT_WithClosures