{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Poppler.Objects.AnnotScreen
    ( 

-- * Exported types
    AnnotScreen(..)                         ,
    IsAnnotScreen                           ,
    toAnnotScreen                           ,
    noAnnotScreen                           ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveAnnotScreenMethod                ,
#endif


-- ** getAction #method:getAction#

#if defined(ENABLE_OVERLOADING)
    AnnotScreenGetActionMethodInfo          ,
#endif
    annotScreenGetAction                    ,




    ) 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.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 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 qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Poppler.Objects.Annot as Poppler.Annot
import {-# SOURCE #-} qualified GI.Poppler.Unions.Action as Poppler.Action

-- | Memory-managed wrapper type.
newtype AnnotScreen = AnnotScreen (ManagedPtr AnnotScreen)
    deriving (AnnotScreen -> AnnotScreen -> Bool
(AnnotScreen -> AnnotScreen -> Bool)
-> (AnnotScreen -> AnnotScreen -> Bool) -> Eq AnnotScreen
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnnotScreen -> AnnotScreen -> Bool
$c/= :: AnnotScreen -> AnnotScreen -> Bool
== :: AnnotScreen -> AnnotScreen -> Bool
$c== :: AnnotScreen -> AnnotScreen -> Bool
Eq)
foreign import ccall "poppler_annot_screen_get_type"
    c_poppler_annot_screen_get_type :: IO GType

instance GObject AnnotScreen where
    gobjectType :: IO GType
gobjectType = IO GType
c_poppler_annot_screen_get_type
    

-- | Convert 'AnnotScreen' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue AnnotScreen where
    toGValue :: AnnotScreen -> IO GValue
toGValue o :: AnnotScreen
o = do
        GType
gtype <- IO GType
c_poppler_annot_screen_get_type
        AnnotScreen -> (Ptr AnnotScreen -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AnnotScreen
o (GType
-> (GValue -> Ptr AnnotScreen -> IO ())
-> Ptr AnnotScreen
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr AnnotScreen -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO AnnotScreen
fromGValue gv :: GValue
gv = do
        Ptr AnnotScreen
ptr <- GValue -> IO (Ptr AnnotScreen)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr AnnotScreen)
        (ManagedPtr AnnotScreen -> AnnotScreen)
-> Ptr AnnotScreen -> IO AnnotScreen
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr AnnotScreen -> AnnotScreen
AnnotScreen Ptr AnnotScreen
ptr
        
    

-- | Type class for types which can be safely cast to `AnnotScreen`, for instance with `toAnnotScreen`.
class (GObject o, O.IsDescendantOf AnnotScreen o) => IsAnnotScreen o
instance (GObject o, O.IsDescendantOf AnnotScreen o) => IsAnnotScreen o

instance O.HasParentTypes AnnotScreen
type instance O.ParentTypes AnnotScreen = '[Poppler.Annot.Annot, GObject.Object.Object]

-- | Cast to `AnnotScreen`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toAnnotScreen :: (MonadIO m, IsAnnotScreen o) => o -> m AnnotScreen
toAnnotScreen :: o -> m AnnotScreen
toAnnotScreen = IO AnnotScreen -> m AnnotScreen
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AnnotScreen -> m AnnotScreen)
-> (o -> IO AnnotScreen) -> o -> m AnnotScreen
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr AnnotScreen -> AnnotScreen) -> o -> IO AnnotScreen
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr AnnotScreen -> AnnotScreen
AnnotScreen

-- | A convenience alias for `Nothing` :: `Maybe` `AnnotScreen`.
noAnnotScreen :: Maybe AnnotScreen
noAnnotScreen :: Maybe AnnotScreen
noAnnotScreen = Maybe AnnotScreen
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveAnnotScreenMethod (t :: Symbol) (o :: *) :: * where
    ResolveAnnotScreenMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveAnnotScreenMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveAnnotScreenMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveAnnotScreenMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveAnnotScreenMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveAnnotScreenMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveAnnotScreenMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveAnnotScreenMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveAnnotScreenMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveAnnotScreenMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveAnnotScreenMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveAnnotScreenMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveAnnotScreenMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveAnnotScreenMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveAnnotScreenMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveAnnotScreenMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveAnnotScreenMethod "getAction" o = AnnotScreenGetActionMethodInfo
    ResolveAnnotScreenMethod "getAnnotType" o = Poppler.Annot.AnnotGetAnnotTypeMethodInfo
    ResolveAnnotScreenMethod "getColor" o = Poppler.Annot.AnnotGetColorMethodInfo
    ResolveAnnotScreenMethod "getContents" o = Poppler.Annot.AnnotGetContentsMethodInfo
    ResolveAnnotScreenMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveAnnotScreenMethod "getFlags" o = Poppler.Annot.AnnotGetFlagsMethodInfo
    ResolveAnnotScreenMethod "getModified" o = Poppler.Annot.AnnotGetModifiedMethodInfo
    ResolveAnnotScreenMethod "getName" o = Poppler.Annot.AnnotGetNameMethodInfo
    ResolveAnnotScreenMethod "getPageIndex" o = Poppler.Annot.AnnotGetPageIndexMethodInfo
    ResolveAnnotScreenMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveAnnotScreenMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveAnnotScreenMethod "getRectangle" o = Poppler.Annot.AnnotGetRectangleMethodInfo
    ResolveAnnotScreenMethod "setColor" o = Poppler.Annot.AnnotSetColorMethodInfo
    ResolveAnnotScreenMethod "setContents" o = Poppler.Annot.AnnotSetContentsMethodInfo
    ResolveAnnotScreenMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveAnnotScreenMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveAnnotScreenMethod "setFlags" o = Poppler.Annot.AnnotSetFlagsMethodInfo
    ResolveAnnotScreenMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveAnnotScreenMethod "setRectangle" o = Poppler.Annot.AnnotSetRectangleMethodInfo
    ResolveAnnotScreenMethod l o = O.MethodResolutionFailed l o

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AnnotScreen
type instance O.AttributeList AnnotScreen = AnnotScreenAttributeList
type AnnotScreenAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList AnnotScreen = AnnotScreenSignalList
type AnnotScreenSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method AnnotScreen::get_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "poppler_annot"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "AnnotScreen" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PopplerAnnotScreen"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Poppler" , name = "Action" })
-- throws : False
-- Skip return : False

foreign import ccall "poppler_annot_screen_get_action" poppler_annot_screen_get_action :: 
    Ptr AnnotScreen ->                      -- poppler_annot : TInterface (Name {namespace = "Poppler", name = "AnnotScreen"})
    IO (Ptr Poppler.Action.Action)

-- | Retrieves the action (t'GI.Poppler.Unions.Action.Action') that shall be performed when /@popplerAnnot@/ is activated
-- 
-- /Since: 0.14/
annotScreenGetAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsAnnotScreen a) =>
    a
    -- ^ /@popplerAnnot@/: a t'GI.Poppler.Objects.AnnotScreen.AnnotScreen'
    -> m Poppler.Action.Action
    -- ^ __Returns:__ the action to perform. The returned
    --               object is owned by /@popplerAnnot@/ and should not be freed
annotScreenGetAction :: a -> m Action
annotScreenGetAction popplerAnnot :: a
popplerAnnot = IO Action -> m Action
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Action -> m Action) -> IO Action -> m Action
forall a b. (a -> b) -> a -> b
$ do
    Ptr AnnotScreen
popplerAnnot' <- a -> IO (Ptr AnnotScreen)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popplerAnnot
    Ptr Action
result <- Ptr AnnotScreen -> IO (Ptr Action)
poppler_annot_screen_get_action Ptr AnnotScreen
popplerAnnot'
    Text -> Ptr Action -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "annotScreenGetAction" Ptr Action
result
    Action
result' <- ((ManagedPtr Action -> Action) -> Ptr Action -> IO Action
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Action -> Action
Poppler.Action.Action) Ptr Action
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popplerAnnot
    Action -> IO Action
forall (m :: * -> *) a. Monad m => a -> m a
return Action
result'

#if defined(ENABLE_OVERLOADING)
data AnnotScreenGetActionMethodInfo
instance (signature ~ (m Poppler.Action.Action), MonadIO m, IsAnnotScreen a) => O.MethodInfo AnnotScreenGetActionMethodInfo a signature where
    overloadedMethod = annotScreenGetAction

#endif