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

module GI.WebKit.Objects.DOMDOMMimeType
    ( 

-- * Exported types
    DOMDOMMimeType(..)                      ,
    DOMDOMMimeTypeK                         ,
    toDOMDOMMimeType                        ,
    noDOMDOMMimeType                        ,


 -- * Methods
-- ** dOMDOMMimeTypeGetDescription
    dOMDOMMimeTypeGetDescription            ,


-- ** dOMDOMMimeTypeGetEnabledPlugin
    dOMDOMMimeTypeGetEnabledPlugin          ,


-- ** dOMDOMMimeTypeGetSuffixes
    dOMDOMMimeTypeGetSuffixes               ,




 -- * Properties
-- ** Description
    DOMDOMMimeTypeDescriptionPropertyInfo   ,
    getDOMDOMMimeTypeDescription            ,


-- ** EnabledPlugin
    DOMDOMMimeTypeEnabledPluginPropertyInfo ,
    getDOMDOMMimeTypeEnabledPlugin          ,


-- ** Suffixes
    DOMDOMMimeTypeSuffixesPropertyInfo      ,
    getDOMDOMMimeTypeSuffixes               ,


-- ** Type
    DOMDOMMimeTypeTypePropertyInfo          ,
    getDOMDOMMimeTypeType                   ,




    ) 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.WebKit.Types
import GI.WebKit.Callbacks
import qualified GI.GObject as GObject

newtype DOMDOMMimeType = DOMDOMMimeType (ForeignPtr DOMDOMMimeType)
foreign import ccall "webkit_dom_dom_mime_type_get_type"
    c_webkit_dom_dom_mime_type_get_type :: IO GType

type instance ParentTypes DOMDOMMimeType = DOMDOMMimeTypeParentTypes
type DOMDOMMimeTypeParentTypes = '[DOMObject, GObject.Object]

instance GObject DOMDOMMimeType where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_webkit_dom_dom_mime_type_get_type
    

class GObject o => DOMDOMMimeTypeK o
instance (GObject o, IsDescendantOf DOMDOMMimeType o) => DOMDOMMimeTypeK o

toDOMDOMMimeType :: DOMDOMMimeTypeK o => o -> IO DOMDOMMimeType
toDOMDOMMimeType = unsafeCastTo DOMDOMMimeType

noDOMDOMMimeType :: Maybe DOMDOMMimeType
noDOMDOMMimeType = Nothing

-- VVV Prop "description"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]

getDOMDOMMimeTypeDescription :: (MonadIO m, DOMDOMMimeTypeK o) => o -> m T.Text
getDOMDOMMimeTypeDescription obj = liftIO $ getObjectPropertyString obj "description"

data DOMDOMMimeTypeDescriptionPropertyInfo
instance AttrInfo DOMDOMMimeTypeDescriptionPropertyInfo where
    type AttrAllowedOps DOMDOMMimeTypeDescriptionPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMDOMMimeTypeDescriptionPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMDOMMimeTypeDescriptionPropertyInfo = DOMDOMMimeTypeK
    type AttrGetType DOMDOMMimeTypeDescriptionPropertyInfo = T.Text
    type AttrLabel DOMDOMMimeTypeDescriptionPropertyInfo = "DOMDOMMimeType::description"
    attrGet _ = getDOMDOMMimeTypeDescription
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "enabled-plugin"
   -- Type: TInterface "WebKit" "DOMDOMPlugin"
   -- Flags: [PropertyReadable]

getDOMDOMMimeTypeEnabledPlugin :: (MonadIO m, DOMDOMMimeTypeK o) => o -> m DOMDOMPlugin
getDOMDOMMimeTypeEnabledPlugin obj = liftIO $ getObjectPropertyObject obj "enabled-plugin" DOMDOMPlugin

data DOMDOMMimeTypeEnabledPluginPropertyInfo
instance AttrInfo DOMDOMMimeTypeEnabledPluginPropertyInfo where
    type AttrAllowedOps DOMDOMMimeTypeEnabledPluginPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMDOMMimeTypeEnabledPluginPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMDOMMimeTypeEnabledPluginPropertyInfo = DOMDOMMimeTypeK
    type AttrGetType DOMDOMMimeTypeEnabledPluginPropertyInfo = DOMDOMPlugin
    type AttrLabel DOMDOMMimeTypeEnabledPluginPropertyInfo = "DOMDOMMimeType::enabled-plugin"
    attrGet _ = getDOMDOMMimeTypeEnabledPlugin
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "suffixes"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]

getDOMDOMMimeTypeSuffixes :: (MonadIO m, DOMDOMMimeTypeK o) => o -> m T.Text
getDOMDOMMimeTypeSuffixes obj = liftIO $ getObjectPropertyString obj "suffixes"

data DOMDOMMimeTypeSuffixesPropertyInfo
instance AttrInfo DOMDOMMimeTypeSuffixesPropertyInfo where
    type AttrAllowedOps DOMDOMMimeTypeSuffixesPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMDOMMimeTypeSuffixesPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMDOMMimeTypeSuffixesPropertyInfo = DOMDOMMimeTypeK
    type AttrGetType DOMDOMMimeTypeSuffixesPropertyInfo = T.Text
    type AttrLabel DOMDOMMimeTypeSuffixesPropertyInfo = "DOMDOMMimeType::suffixes"
    attrGet _ = getDOMDOMMimeTypeSuffixes
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "type"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]

getDOMDOMMimeTypeType :: (MonadIO m, DOMDOMMimeTypeK o) => o -> m T.Text
getDOMDOMMimeTypeType obj = liftIO $ getObjectPropertyString obj "type"

data DOMDOMMimeTypeTypePropertyInfo
instance AttrInfo DOMDOMMimeTypeTypePropertyInfo where
    type AttrAllowedOps DOMDOMMimeTypeTypePropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMDOMMimeTypeTypePropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMDOMMimeTypeTypePropertyInfo = DOMDOMMimeTypeK
    type AttrGetType DOMDOMMimeTypeTypePropertyInfo = T.Text
    type AttrLabel DOMDOMMimeTypeTypePropertyInfo = "DOMDOMMimeType::type"
    attrGet _ = getDOMDOMMimeTypeType
    attrSet _ = undefined
    attrConstruct _ = undefined

type instance AttributeList DOMDOMMimeType = DOMDOMMimeTypeAttributeList
type DOMDOMMimeTypeAttributeList = ('[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("description", DOMDOMMimeTypeDescriptionPropertyInfo), '("enabled-plugin", DOMDOMMimeTypeEnabledPluginPropertyInfo), '("suffixes", DOMDOMMimeTypeSuffixesPropertyInfo), '("type", DOMDOMMimeTypeTypePropertyInfo)] :: [(Symbol, *)])

type instance SignalList DOMDOMMimeType = DOMDOMMimeTypeSignalList
type DOMDOMMimeTypeSignalList = ('[ '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

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

foreign import ccall "webkit_dom_dom_mime_type_get_description" webkit_dom_dom_mime_type_get_description :: 
    Ptr DOMDOMMimeType ->                   -- _obj : TInterface "WebKit" "DOMDOMMimeType"
    IO CString


dOMDOMMimeTypeGetDescription ::
    (MonadIO m, DOMDOMMimeTypeK a) =>
    a ->                                    -- _obj
    m T.Text
dOMDOMMimeTypeGetDescription _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_dom_mime_type_get_description _obj'
    checkUnexpectedReturnNULL "webkit_dom_dom_mime_type_get_description" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method DOMDOMMimeType::get_enabled_plugin
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMDOMMimeType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMDOMMimeType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "WebKit" "DOMDOMPlugin"
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_dom_mime_type_get_enabled_plugin" webkit_dom_dom_mime_type_get_enabled_plugin :: 
    Ptr DOMDOMMimeType ->                   -- _obj : TInterface "WebKit" "DOMDOMMimeType"
    IO (Ptr DOMDOMPlugin)


dOMDOMMimeTypeGetEnabledPlugin ::
    (MonadIO m, DOMDOMMimeTypeK a) =>
    a ->                                    -- _obj
    m DOMDOMPlugin
dOMDOMMimeTypeGetEnabledPlugin _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_dom_mime_type_get_enabled_plugin _obj'
    checkUnexpectedReturnNULL "webkit_dom_dom_mime_type_get_enabled_plugin" result
    result' <- (wrapObject DOMDOMPlugin) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "webkit_dom_dom_mime_type_get_suffixes" webkit_dom_dom_mime_type_get_suffixes :: 
    Ptr DOMDOMMimeType ->                   -- _obj : TInterface "WebKit" "DOMDOMMimeType"
    IO CString


dOMDOMMimeTypeGetSuffixes ::
    (MonadIO m, DOMDOMMimeTypeK a) =>
    a ->                                    -- _obj
    m T.Text
dOMDOMMimeTypeGetSuffixes _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_dom_mime_type_get_suffixes _obj'
    checkUnexpectedReturnNULL "webkit_dom_dom_mime_type_get_suffixes" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'