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

A plugin should export a variable of this type called plugin_desc. The plugin
loader will use the data provided there to initialize the plugin.

The /@licence@/ parameter must be one of: LGPL, GPL, QPL, GPL\/QPL, MPL,
BSD, MIT\/X11, Proprietary, unknown.
-}

module GI.Gst.Structs.PluginDesc
    ( 

-- * Exported types
    PluginDesc(..)                          ,
    newZeroPluginDesc                       ,
    noPluginDesc                            ,


 -- * Properties
-- ** description #attr:description#
    clearPluginDescDescription              ,
    getPluginDescDescription                ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    pluginDesc_description                  ,
#endif
    setPluginDescDescription                ,


-- ** license #attr:license#
    clearPluginDescLicense                  ,
    getPluginDescLicense                    ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    pluginDesc_license                      ,
#endif
    setPluginDescLicense                    ,


-- ** majorVersion #attr:majorVersion#
    getPluginDescMajorVersion               ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    pluginDesc_majorVersion                 ,
#endif
    setPluginDescMajorVersion               ,


-- ** minorVersion #attr:minorVersion#
    getPluginDescMinorVersion               ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    pluginDesc_minorVersion                 ,
#endif
    setPluginDescMinorVersion               ,


-- ** name #attr:name#
    clearPluginDescName                     ,
    getPluginDescName                       ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    pluginDesc_name                         ,
#endif
    setPluginDescName                       ,


-- ** origin #attr:origin#
    clearPluginDescOrigin                   ,
    getPluginDescOrigin                     ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    pluginDesc_origin                       ,
#endif
    setPluginDescOrigin                     ,


-- ** package #attr:package#
    clearPluginDescPackage                  ,
    getPluginDescPackage                    ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    pluginDesc_package                      ,
#endif
    setPluginDescPackage                    ,


-- ** pluginInit #attr:pluginInit#
    clearPluginDescPluginInit               ,
    getPluginDescPluginInit                 ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    pluginDesc_pluginInit                   ,
#endif
    setPluginDescPluginInit                 ,


-- ** releaseDatetime #attr:releaseDatetime#
    clearPluginDescReleaseDatetime          ,
    getPluginDescReleaseDatetime            ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    pluginDesc_releaseDatetime              ,
#endif
    setPluginDescReleaseDatetime            ,


-- ** source #attr:source#
    clearPluginDescSource                   ,
    getPluginDescSource                     ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    pluginDesc_source                       ,
#endif
    setPluginDescSource                     ,


-- ** version #attr:version#
    clearPluginDescVersion                  ,
    getPluginDescVersion                    ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    pluginDesc_version                      ,
#endif
    setPluginDescVersion                    ,




    ) 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
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 GI.Gst.Callbacks as Gst.Callbacks

newtype PluginDesc = PluginDesc (ManagedPtr PluginDesc)
instance WrappedPtr PluginDesc where
    wrappedPtrCalloc = callocBytes 112
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 112 >=> wrapPtr PluginDesc)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `PluginDesc` struct initialized to zero.
newZeroPluginDesc :: MonadIO m => m PluginDesc
newZeroPluginDesc = liftIO $ wrappedPtrCalloc >>= wrapPtr PluginDesc

instance tag ~ 'AttrSet => Constructible PluginDesc tag where
    new _ attrs = do
        o <- newZeroPluginDesc
        GI.Attributes.set o attrs
        return o


noPluginDesc :: Maybe PluginDesc
noPluginDesc = Nothing

getPluginDescMajorVersion :: MonadIO m => PluginDesc -> m Int32
getPluginDescMajorVersion s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Int32
    return val

setPluginDescMajorVersion :: MonadIO m => PluginDesc -> Int32 -> m ()
setPluginDescMajorVersion s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Int32)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data PluginDescMajorVersionFieldInfo
instance AttrInfo PluginDescMajorVersionFieldInfo where
    type AttrAllowedOps PluginDescMajorVersionFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint PluginDescMajorVersionFieldInfo = (~) Int32
    type AttrBaseTypeConstraint PluginDescMajorVersionFieldInfo = (~) PluginDesc
    type AttrGetType PluginDescMajorVersionFieldInfo = Int32
    type AttrLabel PluginDescMajorVersionFieldInfo = "major_version"
    type AttrOrigin PluginDescMajorVersionFieldInfo = PluginDesc
    attrGet _ = getPluginDescMajorVersion
    attrSet _ = setPluginDescMajorVersion
    attrConstruct = undefined
    attrClear _ = undefined

pluginDesc_majorVersion :: AttrLabelProxy "majorVersion"
pluginDesc_majorVersion = AttrLabelProxy

#endif


getPluginDescMinorVersion :: MonadIO m => PluginDesc -> m Int32
getPluginDescMinorVersion s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 4) :: IO Int32
    return val

setPluginDescMinorVersion :: MonadIO m => PluginDesc -> Int32 -> m ()
setPluginDescMinorVersion s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 4) (val :: Int32)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data PluginDescMinorVersionFieldInfo
instance AttrInfo PluginDescMinorVersionFieldInfo where
    type AttrAllowedOps PluginDescMinorVersionFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint PluginDescMinorVersionFieldInfo = (~) Int32
    type AttrBaseTypeConstraint PluginDescMinorVersionFieldInfo = (~) PluginDesc
    type AttrGetType PluginDescMinorVersionFieldInfo = Int32
    type AttrLabel PluginDescMinorVersionFieldInfo = "minor_version"
    type AttrOrigin PluginDescMinorVersionFieldInfo = PluginDesc
    attrGet _ = getPluginDescMinorVersion
    attrSet _ = setPluginDescMinorVersion
    attrConstruct = undefined
    attrClear _ = undefined

pluginDesc_minorVersion :: AttrLabelProxy "minorVersion"
pluginDesc_minorVersion = AttrLabelProxy

#endif


getPluginDescName :: MonadIO m => PluginDesc -> m (Maybe T.Text)
getPluginDescName s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setPluginDescName :: MonadIO m => PluginDesc -> CString -> m ()
setPluginDescName s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: CString)

clearPluginDescName :: MonadIO m => PluginDesc -> m ()
clearPluginDescName s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data PluginDescNameFieldInfo
instance AttrInfo PluginDescNameFieldInfo where
    type AttrAllowedOps PluginDescNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PluginDescNameFieldInfo = (~) CString
    type AttrBaseTypeConstraint PluginDescNameFieldInfo = (~) PluginDesc
    type AttrGetType PluginDescNameFieldInfo = Maybe T.Text
    type AttrLabel PluginDescNameFieldInfo = "name"
    type AttrOrigin PluginDescNameFieldInfo = PluginDesc
    attrGet _ = getPluginDescName
    attrSet _ = setPluginDescName
    attrConstruct = undefined
    attrClear _ = clearPluginDescName

pluginDesc_name :: AttrLabelProxy "name"
pluginDesc_name = AttrLabelProxy

#endif


getPluginDescDescription :: MonadIO m => PluginDesc -> m (Maybe T.Text)
getPluginDescDescription s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setPluginDescDescription :: MonadIO m => PluginDesc -> CString -> m ()
setPluginDescDescription s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: CString)

clearPluginDescDescription :: MonadIO m => PluginDesc -> m ()
clearPluginDescDescription s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data PluginDescDescriptionFieldInfo
instance AttrInfo PluginDescDescriptionFieldInfo where
    type AttrAllowedOps PluginDescDescriptionFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PluginDescDescriptionFieldInfo = (~) CString
    type AttrBaseTypeConstraint PluginDescDescriptionFieldInfo = (~) PluginDesc
    type AttrGetType PluginDescDescriptionFieldInfo = Maybe T.Text
    type AttrLabel PluginDescDescriptionFieldInfo = "description"
    type AttrOrigin PluginDescDescriptionFieldInfo = PluginDesc
    attrGet _ = getPluginDescDescription
    attrSet _ = setPluginDescDescription
    attrConstruct = undefined
    attrClear _ = clearPluginDescDescription

pluginDesc_description :: AttrLabelProxy "description"
pluginDesc_description = AttrLabelProxy

#endif


getPluginDescPluginInit :: MonadIO m => PluginDesc -> m (Maybe Gst.Callbacks.PluginInitFunc)
getPluginDescPluginInit s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO (FunPtr Gst.Callbacks.C_PluginInitFunc)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = Gst.Callbacks.dynamic_PluginInitFunc val'
        return val''
    return result

setPluginDescPluginInit :: MonadIO m => PluginDesc -> FunPtr Gst.Callbacks.C_PluginInitFunc -> m ()
setPluginDescPluginInit s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: FunPtr Gst.Callbacks.C_PluginInitFunc)

clearPluginDescPluginInit :: MonadIO m => PluginDesc -> m ()
clearPluginDescPluginInit s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (FP.nullFunPtr :: FunPtr Gst.Callbacks.C_PluginInitFunc)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data PluginDescPluginInitFieldInfo
instance AttrInfo PluginDescPluginInitFieldInfo where
    type AttrAllowedOps PluginDescPluginInitFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PluginDescPluginInitFieldInfo = (~) (FunPtr Gst.Callbacks.C_PluginInitFunc)
    type AttrBaseTypeConstraint PluginDescPluginInitFieldInfo = (~) PluginDesc
    type AttrGetType PluginDescPluginInitFieldInfo = Maybe Gst.Callbacks.PluginInitFunc
    type AttrLabel PluginDescPluginInitFieldInfo = "plugin_init"
    type AttrOrigin PluginDescPluginInitFieldInfo = PluginDesc
    attrGet _ = getPluginDescPluginInit
    attrSet _ = setPluginDescPluginInit
    attrConstruct = undefined
    attrClear _ = clearPluginDescPluginInit

pluginDesc_pluginInit :: AttrLabelProxy "pluginInit"
pluginDesc_pluginInit = AttrLabelProxy

#endif


getPluginDescVersion :: MonadIO m => PluginDesc -> m (Maybe T.Text)
getPluginDescVersion s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setPluginDescVersion :: MonadIO m => PluginDesc -> CString -> m ()
setPluginDescVersion s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: CString)

clearPluginDescVersion :: MonadIO m => PluginDesc -> m ()
clearPluginDescVersion s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data PluginDescVersionFieldInfo
instance AttrInfo PluginDescVersionFieldInfo where
    type AttrAllowedOps PluginDescVersionFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PluginDescVersionFieldInfo = (~) CString
    type AttrBaseTypeConstraint PluginDescVersionFieldInfo = (~) PluginDesc
    type AttrGetType PluginDescVersionFieldInfo = Maybe T.Text
    type AttrLabel PluginDescVersionFieldInfo = "version"
    type AttrOrigin PluginDescVersionFieldInfo = PluginDesc
    attrGet _ = getPluginDescVersion
    attrSet _ = setPluginDescVersion
    attrConstruct = undefined
    attrClear _ = clearPluginDescVersion

pluginDesc_version :: AttrLabelProxy "version"
pluginDesc_version = AttrLabelProxy

#endif


getPluginDescLicense :: MonadIO m => PluginDesc -> m (Maybe T.Text)
getPluginDescLicense s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setPluginDescLicense :: MonadIO m => PluginDesc -> CString -> m ()
setPluginDescLicense s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (val :: CString)

clearPluginDescLicense :: MonadIO m => PluginDesc -> m ()
clearPluginDescLicense s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data PluginDescLicenseFieldInfo
instance AttrInfo PluginDescLicenseFieldInfo where
    type AttrAllowedOps PluginDescLicenseFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PluginDescLicenseFieldInfo = (~) CString
    type AttrBaseTypeConstraint PluginDescLicenseFieldInfo = (~) PluginDesc
    type AttrGetType PluginDescLicenseFieldInfo = Maybe T.Text
    type AttrLabel PluginDescLicenseFieldInfo = "license"
    type AttrOrigin PluginDescLicenseFieldInfo = PluginDesc
    attrGet _ = getPluginDescLicense
    attrSet _ = setPluginDescLicense
    attrConstruct = undefined
    attrClear _ = clearPluginDescLicense

pluginDesc_license :: AttrLabelProxy "license"
pluginDesc_license = AttrLabelProxy

#endif


getPluginDescSource :: MonadIO m => PluginDesc -> m (Maybe T.Text)
getPluginDescSource s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 48) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setPluginDescSource :: MonadIO m => PluginDesc -> CString -> m ()
setPluginDescSource s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 48) (val :: CString)

clearPluginDescSource :: MonadIO m => PluginDesc -> m ()
clearPluginDescSource s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 48) (FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data PluginDescSourceFieldInfo
instance AttrInfo PluginDescSourceFieldInfo where
    type AttrAllowedOps PluginDescSourceFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PluginDescSourceFieldInfo = (~) CString
    type AttrBaseTypeConstraint PluginDescSourceFieldInfo = (~) PluginDesc
    type AttrGetType PluginDescSourceFieldInfo = Maybe T.Text
    type AttrLabel PluginDescSourceFieldInfo = "source"
    type AttrOrigin PluginDescSourceFieldInfo = PluginDesc
    attrGet _ = getPluginDescSource
    attrSet _ = setPluginDescSource
    attrConstruct = undefined
    attrClear _ = clearPluginDescSource

pluginDesc_source :: AttrLabelProxy "source"
pluginDesc_source = AttrLabelProxy

#endif


getPluginDescPackage :: MonadIO m => PluginDesc -> m (Maybe T.Text)
getPluginDescPackage s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 56) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setPluginDescPackage :: MonadIO m => PluginDesc -> CString -> m ()
setPluginDescPackage s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 56) (val :: CString)

clearPluginDescPackage :: MonadIO m => PluginDesc -> m ()
clearPluginDescPackage s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 56) (FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data PluginDescPackageFieldInfo
instance AttrInfo PluginDescPackageFieldInfo where
    type AttrAllowedOps PluginDescPackageFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PluginDescPackageFieldInfo = (~) CString
    type AttrBaseTypeConstraint PluginDescPackageFieldInfo = (~) PluginDesc
    type AttrGetType PluginDescPackageFieldInfo = Maybe T.Text
    type AttrLabel PluginDescPackageFieldInfo = "package"
    type AttrOrigin PluginDescPackageFieldInfo = PluginDesc
    attrGet _ = getPluginDescPackage
    attrSet _ = setPluginDescPackage
    attrConstruct = undefined
    attrClear _ = clearPluginDescPackage

pluginDesc_package :: AttrLabelProxy "package"
pluginDesc_package = AttrLabelProxy

#endif


getPluginDescOrigin :: MonadIO m => PluginDesc -> m (Maybe T.Text)
getPluginDescOrigin s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 64) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setPluginDescOrigin :: MonadIO m => PluginDesc -> CString -> m ()
setPluginDescOrigin s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 64) (val :: CString)

clearPluginDescOrigin :: MonadIO m => PluginDesc -> m ()
clearPluginDescOrigin s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 64) (FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data PluginDescOriginFieldInfo
instance AttrInfo PluginDescOriginFieldInfo where
    type AttrAllowedOps PluginDescOriginFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PluginDescOriginFieldInfo = (~) CString
    type AttrBaseTypeConstraint PluginDescOriginFieldInfo = (~) PluginDesc
    type AttrGetType PluginDescOriginFieldInfo = Maybe T.Text
    type AttrLabel PluginDescOriginFieldInfo = "origin"
    type AttrOrigin PluginDescOriginFieldInfo = PluginDesc
    attrGet _ = getPluginDescOrigin
    attrSet _ = setPluginDescOrigin
    attrConstruct = undefined
    attrClear _ = clearPluginDescOrigin

pluginDesc_origin :: AttrLabelProxy "origin"
pluginDesc_origin = AttrLabelProxy

#endif


getPluginDescReleaseDatetime :: MonadIO m => PluginDesc -> m (Maybe T.Text)
getPluginDescReleaseDatetime s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 72) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setPluginDescReleaseDatetime :: MonadIO m => PluginDesc -> CString -> m ()
setPluginDescReleaseDatetime s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 72) (val :: CString)

clearPluginDescReleaseDatetime :: MonadIO m => PluginDesc -> m ()
clearPluginDescReleaseDatetime s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 72) (FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data PluginDescReleaseDatetimeFieldInfo
instance AttrInfo PluginDescReleaseDatetimeFieldInfo where
    type AttrAllowedOps PluginDescReleaseDatetimeFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PluginDescReleaseDatetimeFieldInfo = (~) CString
    type AttrBaseTypeConstraint PluginDescReleaseDatetimeFieldInfo = (~) PluginDesc
    type AttrGetType PluginDescReleaseDatetimeFieldInfo = Maybe T.Text
    type AttrLabel PluginDescReleaseDatetimeFieldInfo = "release_datetime"
    type AttrOrigin PluginDescReleaseDatetimeFieldInfo = PluginDesc
    attrGet _ = getPluginDescReleaseDatetime
    attrSet _ = setPluginDescReleaseDatetime
    attrConstruct = undefined
    attrClear _ = clearPluginDescReleaseDatetime

pluginDesc_releaseDatetime :: AttrLabelProxy "releaseDatetime"
pluginDesc_releaseDatetime = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
instance O.HasAttributeList PluginDesc
type instance O.AttributeList PluginDesc = PluginDescAttributeList
type PluginDescAttributeList = ('[ '("majorVersion", PluginDescMajorVersionFieldInfo), '("minorVersion", PluginDescMinorVersionFieldInfo), '("name", PluginDescNameFieldInfo), '("description", PluginDescDescriptionFieldInfo), '("pluginInit", PluginDescPluginInitFieldInfo), '("version", PluginDescVersionFieldInfo), '("license", PluginDescLicenseFieldInfo), '("source", PluginDescSourceFieldInfo), '("package", PluginDescPackageFieldInfo), '("origin", PluginDescOriginFieldInfo), '("releaseDatetime", PluginDescReleaseDatetimeFieldInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
type family ResolvePluginDescMethod (t :: Symbol) (o :: *) :: * where
    ResolvePluginDescMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolvePluginDescMethod t PluginDesc, O.MethodInfo info PluginDesc p) => O.IsLabelProxy t (PluginDesc -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolvePluginDescMethod t PluginDesc, O.MethodInfo info PluginDesc p) => O.IsLabel t (PluginDesc -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif
#endif

#endif