{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Pango.Structs.AttrLanguage.AttrLanguage' structure is used to represent attributes that
-- are languages.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Pango.Structs.AttrLanguage
    ( 

-- * Exported types
    AttrLanguage(..)                        ,
    newZeroAttrLanguage                     ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveAttrLanguageMethod               ,
#endif


-- ** new #method:new#

    attrLanguageNew                         ,




 -- * Properties
-- ** attr #attr:attr#
-- | the common portion of the attribute

#if defined(ENABLE_OVERLOADING)
    attrLanguage_attr                       ,
#endif
    getAttrLanguageAttr                     ,


-- ** value #attr:value#
-- | the t'GI.Pango.Structs.Language.Language' which is the value of the attribute

#if defined(ENABLE_OVERLOADING)
    attrLanguage_value                      ,
#endif
    clearAttrLanguageValue                  ,
    getAttrLanguageValue                    ,
    setAttrLanguageValue                    ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import {-# SOURCE #-} qualified GI.Pango.Structs.Attribute as Pango.Attribute
import {-# SOURCE #-} qualified GI.Pango.Structs.Language as Pango.Language

-- | Memory-managed wrapper type.
newtype AttrLanguage = AttrLanguage (SP.ManagedPtr AttrLanguage)
    deriving (AttrLanguage -> AttrLanguage -> Bool
(AttrLanguage -> AttrLanguage -> Bool)
-> (AttrLanguage -> AttrLanguage -> Bool) -> Eq AttrLanguage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttrLanguage -> AttrLanguage -> Bool
$c/= :: AttrLanguage -> AttrLanguage -> Bool
== :: AttrLanguage -> AttrLanguage -> Bool
$c== :: AttrLanguage -> AttrLanguage -> Bool
Eq)

instance SP.ManagedPtrNewtype AttrLanguage where
    toManagedPtr :: AttrLanguage -> ManagedPtr AttrLanguage
toManagedPtr (AttrLanguage ManagedPtr AttrLanguage
p) = ManagedPtr AttrLanguage
p

instance BoxedPtr AttrLanguage where
    boxedPtrCopy :: AttrLanguage -> IO AttrLanguage
boxedPtrCopy = \AttrLanguage
p -> AttrLanguage
-> (Ptr AttrLanguage -> IO AttrLanguage) -> IO AttrLanguage
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AttrLanguage
p (Int -> Ptr AttrLanguage -> IO (Ptr AttrLanguage)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
24 (Ptr AttrLanguage -> IO (Ptr AttrLanguage))
-> (Ptr AttrLanguage -> IO AttrLanguage)
-> Ptr AttrLanguage
-> IO AttrLanguage
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr AttrLanguage -> AttrLanguage)
-> Ptr AttrLanguage -> IO AttrLanguage
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr AttrLanguage -> AttrLanguage
AttrLanguage)
    boxedPtrFree :: AttrLanguage -> IO ()
boxedPtrFree = \AttrLanguage
x -> AttrLanguage -> (Ptr AttrLanguage -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr AttrLanguage
x Ptr AttrLanguage -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr AttrLanguage where
    boxedPtrCalloc :: IO (Ptr AttrLanguage)
boxedPtrCalloc = Int -> IO (Ptr AttrLanguage)
forall a. Int -> IO (Ptr a)
callocBytes Int
24


-- | Construct a `AttrLanguage` struct initialized to zero.
newZeroAttrLanguage :: MonadIO m => m AttrLanguage
newZeroAttrLanguage :: m AttrLanguage
newZeroAttrLanguage = IO AttrLanguage -> m AttrLanguage
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AttrLanguage -> m AttrLanguage)
-> IO AttrLanguage -> m AttrLanguage
forall a b. (a -> b) -> a -> b
$ IO (Ptr AttrLanguage)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr AttrLanguage)
-> (Ptr AttrLanguage -> IO AttrLanguage) -> IO AttrLanguage
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr AttrLanguage -> AttrLanguage)
-> Ptr AttrLanguage -> IO AttrLanguage
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr AttrLanguage -> AttrLanguage
AttrLanguage

instance tag ~ 'AttrSet => Constructible AttrLanguage tag where
    new :: (ManagedPtr AttrLanguage -> AttrLanguage)
-> [AttrOp AttrLanguage tag] -> m AttrLanguage
new ManagedPtr AttrLanguage -> AttrLanguage
_ [AttrOp AttrLanguage tag]
attrs = do
        AttrLanguage
o <- m AttrLanguage
forall (m :: * -> *). MonadIO m => m AttrLanguage
newZeroAttrLanguage
        AttrLanguage -> [AttrOp AttrLanguage 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set AttrLanguage
o [AttrOp AttrLanguage tag]
[AttrOp AttrLanguage 'AttrSet]
attrs
        AttrLanguage -> m AttrLanguage
forall (m :: * -> *) a. Monad m => a -> m a
return AttrLanguage
o


-- | Get the value of the “@attr@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' attrLanguage #attr
-- @
getAttrLanguageAttr :: MonadIO m => AttrLanguage -> m Pango.Attribute.Attribute
getAttrLanguageAttr :: AttrLanguage -> m Attribute
getAttrLanguageAttr AttrLanguage
s = IO Attribute -> m Attribute
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Attribute -> m Attribute) -> IO Attribute -> m Attribute
forall a b. (a -> b) -> a -> b
$ AttrLanguage -> (Ptr AttrLanguage -> IO Attribute) -> IO Attribute
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrLanguage
s ((Ptr AttrLanguage -> IO Attribute) -> IO Attribute)
-> (Ptr AttrLanguage -> IO Attribute) -> IO Attribute
forall a b. (a -> b) -> a -> b
$ \Ptr AttrLanguage
ptr -> do
    let val :: Ptr Attribute
val = Ptr AttrLanguage
ptr Ptr AttrLanguage -> Int -> Ptr Attribute
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: (Ptr Pango.Attribute.Attribute)
    Attribute
val' <- ((ManagedPtr Attribute -> Attribute)
-> Ptr Attribute -> IO Attribute
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Attribute -> Attribute
Pango.Attribute.Attribute) Ptr Attribute
val
    Attribute -> IO Attribute
forall (m :: * -> *) a. Monad m => a -> m a
return Attribute
val'

#if defined(ENABLE_OVERLOADING)
data AttrLanguageAttrFieldInfo
instance AttrInfo AttrLanguageAttrFieldInfo where
    type AttrBaseTypeConstraint AttrLanguageAttrFieldInfo = (~) AttrLanguage
    type AttrAllowedOps AttrLanguageAttrFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint AttrLanguageAttrFieldInfo = (~) (Ptr Pango.Attribute.Attribute)
    type AttrTransferTypeConstraint AttrLanguageAttrFieldInfo = (~)(Ptr Pango.Attribute.Attribute)
    type AttrTransferType AttrLanguageAttrFieldInfo = (Ptr Pango.Attribute.Attribute)
    type AttrGetType AttrLanguageAttrFieldInfo = Pango.Attribute.Attribute
    type AttrLabel AttrLanguageAttrFieldInfo = "attr"
    type AttrOrigin AttrLanguageAttrFieldInfo = AttrLanguage
    attrGet = getAttrLanguageAttr
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined

attrLanguage_attr :: AttrLabelProxy "attr"
attrLanguage_attr = AttrLabelProxy

#endif


-- | Get the value of the “@value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' attrLanguage #value
-- @
getAttrLanguageValue :: MonadIO m => AttrLanguage -> m (Maybe Pango.Language.Language)
getAttrLanguageValue :: AttrLanguage -> m (Maybe Language)
getAttrLanguageValue AttrLanguage
s = IO (Maybe Language) -> m (Maybe Language)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Language) -> m (Maybe Language))
-> IO (Maybe Language) -> m (Maybe Language)
forall a b. (a -> b) -> a -> b
$ AttrLanguage
-> (Ptr AttrLanguage -> IO (Maybe Language)) -> IO (Maybe Language)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrLanguage
s ((Ptr AttrLanguage -> IO (Maybe Language)) -> IO (Maybe Language))
-> (Ptr AttrLanguage -> IO (Maybe Language)) -> IO (Maybe Language)
forall a b. (a -> b) -> a -> b
$ \Ptr AttrLanguage
ptr -> do
    Ptr Language
val <- Ptr (Ptr Language) -> IO (Ptr Language)
forall a. Storable a => Ptr a -> IO a
peek (Ptr AttrLanguage
ptr Ptr AttrLanguage -> Int -> Ptr (Ptr Language)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO (Ptr Pango.Language.Language)
    Maybe Language
result <- Ptr Language
-> (Ptr Language -> IO Language) -> IO (Maybe Language)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Language
val ((Ptr Language -> IO Language) -> IO (Maybe Language))
-> (Ptr Language -> IO Language) -> IO (Maybe Language)
forall a b. (a -> b) -> a -> b
$ \Ptr Language
val' -> do
        Language
val'' <- ((ManagedPtr Language -> Language) -> Ptr Language -> IO Language
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Language -> Language
Pango.Language.Language) Ptr Language
val'
        Language -> IO Language
forall (m :: * -> *) a. Monad m => a -> m a
return Language
val''
    Maybe Language -> IO (Maybe Language)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Language
result

-- | Set the value of the “@value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' attrLanguage [ #value 'Data.GI.Base.Attributes.:=' value ]
-- @
setAttrLanguageValue :: MonadIO m => AttrLanguage -> Ptr Pango.Language.Language -> m ()
setAttrLanguageValue :: AttrLanguage -> Ptr Language -> m ()
setAttrLanguageValue AttrLanguage
s Ptr Language
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ AttrLanguage -> (Ptr AttrLanguage -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrLanguage
s ((Ptr AttrLanguage -> IO ()) -> IO ())
-> (Ptr AttrLanguage -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AttrLanguage
ptr -> do
    Ptr (Ptr Language) -> Ptr Language -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AttrLanguage
ptr Ptr AttrLanguage -> Int -> Ptr (Ptr Language)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Ptr Language
val :: Ptr Pango.Language.Language)

-- | Set the value of the “@value@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #value
-- @
clearAttrLanguageValue :: MonadIO m => AttrLanguage -> m ()
clearAttrLanguageValue :: AttrLanguage -> m ()
clearAttrLanguageValue AttrLanguage
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ AttrLanguage -> (Ptr AttrLanguage -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrLanguage
s ((Ptr AttrLanguage -> IO ()) -> IO ())
-> (Ptr AttrLanguage -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AttrLanguage
ptr -> do
    Ptr (Ptr Language) -> Ptr Language -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AttrLanguage
ptr Ptr AttrLanguage -> Int -> Ptr (Ptr Language)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Ptr Language
forall a. Ptr a
FP.nullPtr :: Ptr Pango.Language.Language)

#if defined(ENABLE_OVERLOADING)
data AttrLanguageValueFieldInfo
instance AttrInfo AttrLanguageValueFieldInfo where
    type AttrBaseTypeConstraint AttrLanguageValueFieldInfo = (~) AttrLanguage
    type AttrAllowedOps AttrLanguageValueFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint AttrLanguageValueFieldInfo = (~) (Ptr Pango.Language.Language)
    type AttrTransferTypeConstraint AttrLanguageValueFieldInfo = (~)(Ptr Pango.Language.Language)
    type AttrTransferType AttrLanguageValueFieldInfo = (Ptr Pango.Language.Language)
    type AttrGetType AttrLanguageValueFieldInfo = Maybe Pango.Language.Language
    type AttrLabel AttrLanguageValueFieldInfo = "value"
    type AttrOrigin AttrLanguageValueFieldInfo = AttrLanguage
    attrGet = getAttrLanguageValue
    attrSet = setAttrLanguageValue
    attrConstruct = undefined
    attrClear = clearAttrLanguageValue
    attrTransfer _ v = do
        return v

attrLanguage_value :: AttrLabelProxy "value"
attrLanguage_value = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AttrLanguage
type instance O.AttributeList AttrLanguage = AttrLanguageAttributeList
type AttrLanguageAttributeList = ('[ '("attr", AttrLanguageAttrFieldInfo), '("value", AttrLanguageValueFieldInfo)] :: [(Symbol, *)])
#endif

-- method AttrLanguage::new
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "language"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Language" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "language tag" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "Attribute" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_language_new" pango_attr_language_new :: 
    Ptr Pango.Language.Language ->          -- language : TInterface (Name {namespace = "Pango", name = "Language"})
    IO (Ptr Pango.Attribute.Attribute)

-- | Create a new language tag attribute.
attrLanguageNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Pango.Language.Language
    -- ^ /@language@/: language tag
    -> m Pango.Attribute.Attribute
    -- ^ __Returns:__ the newly allocated t'GI.Pango.Structs.Attribute.Attribute',
    --               which should be freed with 'GI.Pango.Structs.Attribute.attributeDestroy'.
attrLanguageNew :: Language -> m Attribute
attrLanguageNew Language
language = IO Attribute -> m Attribute
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Attribute -> m Attribute) -> IO Attribute -> m Attribute
forall a b. (a -> b) -> a -> b
$ do
    Ptr Language
language' <- Language -> IO (Ptr Language)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Language
language
    Ptr Attribute
result <- Ptr Language -> IO (Ptr Attribute)
pango_attr_language_new Ptr Language
language'
    Text -> Ptr Attribute -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"attrLanguageNew" Ptr Attribute
result
    Attribute
result' <- ((ManagedPtr Attribute -> Attribute)
-> Ptr Attribute -> IO Attribute
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Attribute -> Attribute
Pango.Attribute.Attribute) Ptr Attribute
result
    Language -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Language
language
    Attribute -> IO Attribute
forall (m :: * -> *) a. Monad m => a -> m a
return Attribute
result'

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveAttrLanguageMethod (t :: Symbol) (o :: *) :: * where
    ResolveAttrLanguageMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveAttrLanguageMethod t AttrLanguage, O.MethodInfo info AttrLanguage p) => OL.IsLabel t (AttrLanguage -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif