{-# LINE 1 "FreeType/Format/BDF/Internal.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}

module FreeType.Format.BDF.Internal
  ( -- ** FT_Get_BDF_Charset_ID
    ft_Get_BDF_Charset_ID'
    -- ** FT_Get_BDF_Property
  , ft_Get_BDF_Property'
  ) where

import           FreeType.Core.Base.Types
import           FreeType.Core.Types.Types
import           FreeType.Format.BDF.Types

import           Data.Int
import           Foreign.Ptr




foreign import ccall "FT_Get_BDF_Charset_ID"
  ft_Get_BDF_Charset_ID'
    :: FT_Face                -- ^ face
    -> Ptr (Ptr Int8) -- ^ acharset_encoding
{-# LINE 24 "FreeType/Format/BDF/Internal.hsc" #-}
    -> Ptr (Ptr Int8) -- ^ acharset_registry
{-# LINE 25 "FreeType/Format/BDF/Internal.hsc" #-}
    -> IO FT_Error



foreign import ccall "FT_Get_BDF_Property"
  ft_Get_BDF_Property'
    :: FT_Face             -- ^ face
    -> Ptr Int8    -- ^ prop_name
{-# LINE 33 "FreeType/Format/BDF/Internal.hsc" #-}
    -> Ptr BDF_PropertyRec -- ^ aproperty
    -> IO FT_Error