{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)

The #PangoLanguage structure is used to
represent a language.

#PangoLanguage pointers can be efficiently
copied and compared with each other.
-}

module GI.Pango.Structs.Language
    ( 

-- * Exported types
    Language(..)                            ,
    noLanguage                              ,


 -- * Methods
-- ** languageGetSampleString
    languageGetSampleString                 ,


-- ** languageGetScripts
    languageGetScripts                      ,


-- ** languageIncludesScript
    languageIncludesScript                  ,


-- ** languageMatches
    languageMatches                         ,


-- ** languageToString
    languageToString                        ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Pango.Types
import GI.Pango.Callbacks

newtype Language = Language (ForeignPtr Language)
foreign import ccall "pango_language_get_type" c_pango_language_get_type :: 
    IO GType

instance BoxedObject Language where
    boxedType _ = c_pango_language_get_type

noLanguage :: Maybe Language
noLanguage = Nothing

-- method Language::get_sample_string
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Language", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Language", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "pango_language_get_sample_string" pango_language_get_sample_string :: 
    Ptr Language ->                         -- _obj : TInterface "Pango" "Language"
    IO CString


languageGetSampleString ::
    (MonadIO m) =>
    Language ->                             -- _obj
    m T.Text
languageGetSampleString _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- pango_language_get_sample_string _obj'
    checkUnexpectedReturnNULL "pango_language_get_sample_string" result
    result' <- cstringToText result
    touchManagedPtr _obj
    return result'

-- method Language::get_scripts
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Language", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "num_scripts", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : [Arg {argName = "num_scripts", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Language", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TCArray False (-1) 1 (TInterface "Pango" "Script")
-- throws : False
-- Skip return : False

foreign import ccall "pango_language_get_scripts" pango_language_get_scripts :: 
    Ptr Language ->                         -- _obj : TInterface "Pango" "Language"
    Ptr Int32 ->                            -- num_scripts : TBasicType TInt32
    IO (Ptr CUInt)


languageGetScripts ::
    (MonadIO m) =>
    Language ->                             -- _obj
    m [Script]
languageGetScripts _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    num_scripts <- allocMem :: IO (Ptr Int32)
    result <- pango_language_get_scripts _obj' num_scripts
    num_scripts' <- peek num_scripts
    checkUnexpectedReturnNULL "pango_language_get_scripts" result
    result' <- (unpackStorableArrayWithLength num_scripts') result
    let result'' = map (toEnum . fromIntegral) result'
    touchManagedPtr _obj
    freeMem num_scripts
    return result''

-- method Language::includes_script
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Language", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "script", argType = TInterface "Pango" "Script", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Language", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "script", argType = TInterface "Pango" "Script", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "pango_language_includes_script" pango_language_includes_script :: 
    Ptr Language ->                         -- _obj : TInterface "Pango" "Language"
    CUInt ->                                -- script : TInterface "Pango" "Script"
    IO CInt


languageIncludesScript ::
    (MonadIO m) =>
    Language ->                             -- _obj
    Script ->                               -- script
    m Bool
languageIncludesScript _obj script = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let script' = (fromIntegral . fromEnum) script
    result <- pango_language_includes_script _obj' script'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method Language::matches
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Language", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "range_list", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Language", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "range_list", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "pango_language_matches" pango_language_matches :: 
    Ptr Language ->                         -- _obj : TInterface "Pango" "Language"
    CString ->                              -- range_list : TBasicType TUTF8
    IO CInt


languageMatches ::
    (MonadIO m) =>
    Language ->                             -- _obj
    T.Text ->                               -- range_list
    m Bool
languageMatches _obj range_list = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    range_list' <- textToCString range_list
    result <- pango_language_matches _obj' range_list'
    let result' = (/= 0) result
    touchManagedPtr _obj
    freeMem range_list'
    return result'

-- method Language::to_string
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Language", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Language", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "pango_language_to_string" pango_language_to_string :: 
    Ptr Language ->                         -- _obj : TInterface "Pango" "Language"
    IO CString


languageToString ::
    (MonadIO m) =>
    Language ->                             -- _obj
    m T.Text
languageToString _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- pango_language_to_string _obj'
    checkUnexpectedReturnNULL "pango_language_to_string" result
    result' <- cstringToText result
    touchManagedPtr _obj
    return result'