{-# 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.WebKit2.Objects.GeolocationManager
    ( 

-- * Exported types
    GeolocationManager(..)                  ,
    IsGeolocationManager                    ,
    toGeolocationManager                    ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [failed]("GI.WebKit2.Objects.GeolocationManager#g:method:failed"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [updatePosition]("GI.WebKit2.Objects.GeolocationManager#g:method:updatePosition"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getEnableHighAccuracy]("GI.WebKit2.Objects.GeolocationManager#g:method:getEnableHighAccuracy"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveGeolocationManagerMethod         ,
#endif

-- ** failed #method:failed#

#if defined(ENABLE_OVERLOADING)
    GeolocationManagerFailedMethodInfo      ,
#endif
    geolocationManagerFailed                ,


-- ** getEnableHighAccuracy #method:getEnableHighAccuracy#

#if defined(ENABLE_OVERLOADING)
    GeolocationManagerGetEnableHighAccuracyMethodInfo,
#endif
    geolocationManagerGetEnableHighAccuracy ,


-- ** updatePosition #method:updatePosition#

#if defined(ENABLE_OVERLOADING)
    GeolocationManagerUpdatePositionMethodInfo,
#endif
    geolocationManagerUpdatePosition        ,




 -- * Properties


-- ** enableHighAccuracy #attr:enableHighAccuracy#
-- | Whether high accuracy is enabled. This is a read-only property that will be
-- set to 'P.True' when a t'GI.WebKit2.Objects.GeolocationManager.GeolocationManager' needs to get accurate position updates.
-- You can connect to notify[enableHighAccuracy](#g:signal:enableHighAccuracy) signal to monitor it.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    GeolocationManagerEnableHighAccuracyPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    geolocationManagerEnableHighAccuracy    ,
#endif
    getGeolocationManagerEnableHighAccuracy ,




 -- * Signals


-- ** start #signal:start#

    C_GeolocationManagerStartCallback       ,
    GeolocationManagerStartCallback         ,
#if defined(ENABLE_OVERLOADING)
    GeolocationManagerStartSignalInfo       ,
#endif
    afterGeolocationManagerStart            ,
    genClosure_GeolocationManagerStart      ,
    mk_GeolocationManagerStartCallback      ,
    noGeolocationManagerStartCallback       ,
    onGeolocationManagerStart               ,
    wrap_GeolocationManagerStartCallback    ,


-- ** stop #signal:stop#

    C_GeolocationManagerStopCallback        ,
    GeolocationManagerStopCallback          ,
#if defined(ENABLE_OVERLOADING)
    GeolocationManagerStopSignalInfo        ,
#endif
    afterGeolocationManagerStop             ,
    genClosure_GeolocationManagerStop       ,
    mk_GeolocationManagerStopCallback       ,
    noGeolocationManagerStopCallback        ,
    onGeolocationManagerStop                ,
    wrap_GeolocationManagerStopCallback     ,




    ) 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.GArray as B.GArray
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 qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.WebKit2.Structs.GeolocationPosition as WebKit2.GeolocationPosition

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

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

foreign import ccall "webkit_geolocation_manager_get_type"
    c_webkit_geolocation_manager_get_type :: IO B.Types.GType

instance B.Types.TypedObject GeolocationManager where
    glibType :: IO GType
glibType = IO GType
c_webkit_geolocation_manager_get_type

instance B.Types.GObject GeolocationManager

-- | Type class for types which can be safely cast to `GeolocationManager`, for instance with `toGeolocationManager`.
class (SP.GObject o, O.IsDescendantOf GeolocationManager o) => IsGeolocationManager o
instance (SP.GObject o, O.IsDescendantOf GeolocationManager o) => IsGeolocationManager o

instance O.HasParentTypes GeolocationManager
type instance O.ParentTypes GeolocationManager = '[GObject.Object.Object]

-- | Cast to `GeolocationManager`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toGeolocationManager :: (MIO.MonadIO m, IsGeolocationManager o) => o -> m GeolocationManager
toGeolocationManager :: forall (m :: * -> *) o.
(MonadIO m, IsGeolocationManager o) =>
o -> m GeolocationManager
toGeolocationManager = IO GeolocationManager -> m GeolocationManager
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO GeolocationManager -> m GeolocationManager)
-> (o -> IO GeolocationManager) -> o -> m GeolocationManager
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr GeolocationManager -> GeolocationManager)
-> o -> IO GeolocationManager
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr GeolocationManager -> GeolocationManager
GeolocationManager

-- | Convert 'GeolocationManager' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe GeolocationManager) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_webkit_geolocation_manager_get_type
    gvalueSet_ :: Ptr GValue -> Maybe GeolocationManager -> IO ()
gvalueSet_ Ptr GValue
gv Maybe GeolocationManager
P.Nothing = Ptr GValue -> Ptr GeolocationManager -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr GeolocationManager
forall a. Ptr a
FP.nullPtr :: FP.Ptr GeolocationManager)
    gvalueSet_ Ptr GValue
gv (P.Just GeolocationManager
obj) = GeolocationManager -> (Ptr GeolocationManager -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr GeolocationManager
obj (Ptr GValue -> Ptr GeolocationManager -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe GeolocationManager)
gvalueGet_ Ptr GValue
gv = do
        Ptr GeolocationManager
ptr <- Ptr GValue -> IO (Ptr GeolocationManager)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr GeolocationManager)
        if Ptr GeolocationManager
ptr Ptr GeolocationManager -> Ptr GeolocationManager -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr GeolocationManager
forall a. Ptr a
FP.nullPtr
        then GeolocationManager -> Maybe GeolocationManager
forall a. a -> Maybe a
P.Just (GeolocationManager -> Maybe GeolocationManager)
-> IO GeolocationManager -> IO (Maybe GeolocationManager)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr GeolocationManager -> GeolocationManager)
-> Ptr GeolocationManager -> IO GeolocationManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr GeolocationManager -> GeolocationManager
GeolocationManager Ptr GeolocationManager
ptr
        else Maybe GeolocationManager -> IO (Maybe GeolocationManager)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GeolocationManager
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveGeolocationManagerMethod (t :: Symbol) (o :: *) :: * where
    ResolveGeolocationManagerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveGeolocationManagerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveGeolocationManagerMethod "failed" o = GeolocationManagerFailedMethodInfo
    ResolveGeolocationManagerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveGeolocationManagerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveGeolocationManagerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveGeolocationManagerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveGeolocationManagerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveGeolocationManagerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveGeolocationManagerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveGeolocationManagerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveGeolocationManagerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveGeolocationManagerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveGeolocationManagerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveGeolocationManagerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveGeolocationManagerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveGeolocationManagerMethod "updatePosition" o = GeolocationManagerUpdatePositionMethodInfo
    ResolveGeolocationManagerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveGeolocationManagerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveGeolocationManagerMethod "getEnableHighAccuracy" o = GeolocationManagerGetEnableHighAccuracyMethodInfo
    ResolveGeolocationManagerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveGeolocationManagerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveGeolocationManagerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveGeolocationManagerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveGeolocationManagerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveGeolocationManagerMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveGeolocationManagerMethod t GeolocationManager, O.OverloadedMethod info GeolocationManager p, R.HasField t GeolocationManager p) => R.HasField t GeolocationManager p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveGeolocationManagerMethod t GeolocationManager, O.OverloadedMethodInfo info GeolocationManager) => OL.IsLabel t (O.MethodProxy info GeolocationManager) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- signal GeolocationManager::start
-- | The signal is emitted to notify that /@manager@/ needs to start receiving
-- position updates. After this signal is emitted the user should provide
-- the updates using 'GI.WebKit2.Objects.GeolocationManager.geolocationManagerUpdatePosition' every time
-- the position changes, or use 'GI.WebKit2.Objects.GeolocationManager.geolocationManagerFailed' in case
-- it isn\'t possible to determine the current position.
-- 
-- If the signal is not handled, WebKit will try to determine the position
-- using GeoClue if available.
-- 
-- /Since: 2.26/
type GeolocationManagerStartCallback =
    IO Bool
    -- ^ __Returns:__ 'P.True' to stop other handlers from being invoked for the event.
    --    'P.False' to propagate the event further.

-- | A convenience synonym for @`Nothing` :: `Maybe` `GeolocationManagerStartCallback`@.
noGeolocationManagerStartCallback :: Maybe GeolocationManagerStartCallback
noGeolocationManagerStartCallback :: Maybe GeolocationManagerStartCallback
noGeolocationManagerStartCallback = Maybe GeolocationManagerStartCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_GeolocationManagerStartCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO CInt

-- | Generate a function pointer callable from C code, from a `C_GeolocationManagerStartCallback`.
foreign import ccall "wrapper"
    mk_GeolocationManagerStartCallback :: C_GeolocationManagerStartCallback -> IO (FunPtr C_GeolocationManagerStartCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_GeolocationManagerStart :: MonadIO m => GeolocationManagerStartCallback -> m (GClosure C_GeolocationManagerStartCallback)
genClosure_GeolocationManagerStart :: forall (m :: * -> *).
MonadIO m =>
GeolocationManagerStartCallback
-> m (GClosure C_GeolocationManagerStartCallback)
genClosure_GeolocationManagerStart GeolocationManagerStartCallback
cb = IO (GClosure C_GeolocationManagerStartCallback)
-> m (GClosure C_GeolocationManagerStartCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_GeolocationManagerStartCallback)
 -> m (GClosure C_GeolocationManagerStartCallback))
-> IO (GClosure C_GeolocationManagerStartCallback)
-> m (GClosure C_GeolocationManagerStartCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_GeolocationManagerStartCallback
cb' = GeolocationManagerStartCallback
-> C_GeolocationManagerStartCallback
wrap_GeolocationManagerStartCallback GeolocationManagerStartCallback
cb
    C_GeolocationManagerStartCallback
-> IO (FunPtr C_GeolocationManagerStartCallback)
mk_GeolocationManagerStartCallback C_GeolocationManagerStartCallback
cb' IO (FunPtr C_GeolocationManagerStartCallback)
-> (FunPtr C_GeolocationManagerStartCallback
    -> IO (GClosure C_GeolocationManagerStartCallback))
-> IO (GClosure C_GeolocationManagerStartCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_GeolocationManagerStartCallback
-> IO (GClosure C_GeolocationManagerStartCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `GeolocationManagerStartCallback` into a `C_GeolocationManagerStartCallback`.
wrap_GeolocationManagerStartCallback ::
    GeolocationManagerStartCallback ->
    C_GeolocationManagerStartCallback
wrap_GeolocationManagerStartCallback :: GeolocationManagerStartCallback
-> C_GeolocationManagerStartCallback
wrap_GeolocationManagerStartCallback GeolocationManagerStartCallback
_cb Ptr ()
_ Ptr ()
_ = do
    Bool
result <- GeolocationManagerStartCallback
_cb 
    let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
result
    CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- | Connect a signal handler for the [start](#signal:start) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' geolocationManager #start callback
-- @
-- 
-- 
onGeolocationManagerStart :: (IsGeolocationManager a, MonadIO m) => a -> GeolocationManagerStartCallback -> m SignalHandlerId
onGeolocationManagerStart :: forall a (m :: * -> *).
(IsGeolocationManager a, MonadIO m) =>
a -> GeolocationManagerStartCallback -> m SignalHandlerId
onGeolocationManagerStart a
obj GeolocationManagerStartCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_GeolocationManagerStartCallback
cb' = GeolocationManagerStartCallback
-> C_GeolocationManagerStartCallback
wrap_GeolocationManagerStartCallback GeolocationManagerStartCallback
cb
    FunPtr C_GeolocationManagerStartCallback
cb'' <- C_GeolocationManagerStartCallback
-> IO (FunPtr C_GeolocationManagerStartCallback)
mk_GeolocationManagerStartCallback C_GeolocationManagerStartCallback
cb'
    a
-> Text
-> FunPtr C_GeolocationManagerStartCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"start" FunPtr C_GeolocationManagerStartCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [start](#signal:start) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' geolocationManager #start callback
-- @
-- 
-- 
afterGeolocationManagerStart :: (IsGeolocationManager a, MonadIO m) => a -> GeolocationManagerStartCallback -> m SignalHandlerId
afterGeolocationManagerStart :: forall a (m :: * -> *).
(IsGeolocationManager a, MonadIO m) =>
a -> GeolocationManagerStartCallback -> m SignalHandlerId
afterGeolocationManagerStart a
obj GeolocationManagerStartCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_GeolocationManagerStartCallback
cb' = GeolocationManagerStartCallback
-> C_GeolocationManagerStartCallback
wrap_GeolocationManagerStartCallback GeolocationManagerStartCallback
cb
    FunPtr C_GeolocationManagerStartCallback
cb'' <- C_GeolocationManagerStartCallback
-> IO (FunPtr C_GeolocationManagerStartCallback)
mk_GeolocationManagerStartCallback C_GeolocationManagerStartCallback
cb'
    a
-> Text
-> FunPtr C_GeolocationManagerStartCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"start" FunPtr C_GeolocationManagerStartCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data GeolocationManagerStartSignalInfo
instance SignalInfo GeolocationManagerStartSignalInfo where
    type HaskellCallbackType GeolocationManagerStartSignalInfo = GeolocationManagerStartCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_GeolocationManagerStartCallback cb
        cb'' <- mk_GeolocationManagerStartCallback cb'
        connectSignalFunPtr obj "start" cb'' connectMode detail

#endif

-- signal GeolocationManager::stop
-- | The signal is emitted to notify that /@manager@/ doesn\'t need to receive
-- position updates anymore.
-- 
-- /Since: 2.26/
type GeolocationManagerStopCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `GeolocationManagerStopCallback`@.
noGeolocationManagerStopCallback :: Maybe GeolocationManagerStopCallback
noGeolocationManagerStopCallback :: Maybe (IO ())
noGeolocationManagerStopCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_GeolocationManagerStopCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_GeolocationManagerStopCallback`.
foreign import ccall "wrapper"
    mk_GeolocationManagerStopCallback :: C_GeolocationManagerStopCallback -> IO (FunPtr C_GeolocationManagerStopCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_GeolocationManagerStop :: MonadIO m => GeolocationManagerStopCallback -> m (GClosure C_GeolocationManagerStopCallback)
genClosure_GeolocationManagerStop :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_GeolocationManagerStopCallback)
genClosure_GeolocationManagerStop IO ()
cb = IO (GClosure C_GeolocationManagerStopCallback)
-> m (GClosure C_GeolocationManagerStopCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_GeolocationManagerStopCallback)
 -> m (GClosure C_GeolocationManagerStopCallback))
-> IO (GClosure C_GeolocationManagerStopCallback)
-> m (GClosure C_GeolocationManagerStopCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_GeolocationManagerStopCallback
cb' = IO () -> C_GeolocationManagerStopCallback
wrap_GeolocationManagerStopCallback IO ()
cb
    C_GeolocationManagerStopCallback
-> IO (FunPtr C_GeolocationManagerStopCallback)
mk_GeolocationManagerStopCallback C_GeolocationManagerStopCallback
cb' IO (FunPtr C_GeolocationManagerStopCallback)
-> (FunPtr C_GeolocationManagerStopCallback
    -> IO (GClosure C_GeolocationManagerStopCallback))
-> IO (GClosure C_GeolocationManagerStopCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_GeolocationManagerStopCallback
-> IO (GClosure C_GeolocationManagerStopCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `GeolocationManagerStopCallback` into a `C_GeolocationManagerStopCallback`.
wrap_GeolocationManagerStopCallback ::
    GeolocationManagerStopCallback ->
    C_GeolocationManagerStopCallback
wrap_GeolocationManagerStopCallback :: IO () -> C_GeolocationManagerStopCallback
wrap_GeolocationManagerStopCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [stop](#signal:stop) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' geolocationManager #stop callback
-- @
-- 
-- 
onGeolocationManagerStop :: (IsGeolocationManager a, MonadIO m) => a -> GeolocationManagerStopCallback -> m SignalHandlerId
onGeolocationManagerStop :: forall a (m :: * -> *).
(IsGeolocationManager a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onGeolocationManagerStop a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_GeolocationManagerStopCallback
cb' = IO () -> C_GeolocationManagerStopCallback
wrap_GeolocationManagerStopCallback IO ()
cb
    FunPtr C_GeolocationManagerStopCallback
cb'' <- C_GeolocationManagerStopCallback
-> IO (FunPtr C_GeolocationManagerStopCallback)
mk_GeolocationManagerStopCallback C_GeolocationManagerStopCallback
cb'
    a
-> Text
-> FunPtr C_GeolocationManagerStopCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"stop" FunPtr C_GeolocationManagerStopCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [stop](#signal:stop) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' geolocationManager #stop callback
-- @
-- 
-- 
afterGeolocationManagerStop :: (IsGeolocationManager a, MonadIO m) => a -> GeolocationManagerStopCallback -> m SignalHandlerId
afterGeolocationManagerStop :: forall a (m :: * -> *).
(IsGeolocationManager a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterGeolocationManagerStop a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_GeolocationManagerStopCallback
cb' = IO () -> C_GeolocationManagerStopCallback
wrap_GeolocationManagerStopCallback IO ()
cb
    FunPtr C_GeolocationManagerStopCallback
cb'' <- C_GeolocationManagerStopCallback
-> IO (FunPtr C_GeolocationManagerStopCallback)
mk_GeolocationManagerStopCallback C_GeolocationManagerStopCallback
cb'
    a
-> Text
-> FunPtr C_GeolocationManagerStopCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"stop" FunPtr C_GeolocationManagerStopCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data GeolocationManagerStopSignalInfo
instance SignalInfo GeolocationManagerStopSignalInfo where
    type HaskellCallbackType GeolocationManagerStopSignalInfo = GeolocationManagerStopCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_GeolocationManagerStopCallback cb
        cb'' <- mk_GeolocationManagerStopCallback cb'
        connectSignalFunPtr obj "stop" cb'' connectMode detail

#endif

-- VVV Prop "enable-high-accuracy"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@enable-high-accuracy@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' geolocationManager #enableHighAccuracy
-- @
getGeolocationManagerEnableHighAccuracy :: (MonadIO m, IsGeolocationManager o) => o -> m Bool
getGeolocationManagerEnableHighAccuracy :: forall (m :: * -> *) o.
(MonadIO m, IsGeolocationManager o) =>
o -> m Bool
getGeolocationManagerEnableHighAccuracy o
obj = GeolocationManagerStartCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (GeolocationManagerStartCallback -> m Bool)
-> GeolocationManagerStartCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> GeolocationManagerStartCallback
forall a.
GObject a =>
a -> String -> GeolocationManagerStartCallback
B.Properties.getObjectPropertyBool o
obj String
"enable-high-accuracy"

#if defined(ENABLE_OVERLOADING)
data GeolocationManagerEnableHighAccuracyPropertyInfo
instance AttrInfo GeolocationManagerEnableHighAccuracyPropertyInfo where
    type AttrAllowedOps GeolocationManagerEnableHighAccuracyPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint GeolocationManagerEnableHighAccuracyPropertyInfo = IsGeolocationManager
    type AttrSetTypeConstraint GeolocationManagerEnableHighAccuracyPropertyInfo = (~) ()
    type AttrTransferTypeConstraint GeolocationManagerEnableHighAccuracyPropertyInfo = (~) ()
    type AttrTransferType GeolocationManagerEnableHighAccuracyPropertyInfo = ()
    type AttrGetType GeolocationManagerEnableHighAccuracyPropertyInfo = Bool
    type AttrLabel GeolocationManagerEnableHighAccuracyPropertyInfo = "enable-high-accuracy"
    type AttrOrigin GeolocationManagerEnableHighAccuracyPropertyInfo = GeolocationManager
    attrGet = getGeolocationManagerEnableHighAccuracy
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GeolocationManager
type instance O.AttributeList GeolocationManager = GeolocationManagerAttributeList
type GeolocationManagerAttributeList = ('[ '("enableHighAccuracy", GeolocationManagerEnableHighAccuracyPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
geolocationManagerEnableHighAccuracy :: AttrLabelProxy "enableHighAccuracy"
geolocationManagerEnableHighAccuracy = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList GeolocationManager = GeolocationManagerSignalList
type GeolocationManagerSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("start", GeolocationManagerStartSignalInfo), '("stop", GeolocationManagerStopSignalInfo)] :: [(Symbol, *)])

#endif

-- method GeolocationManager::failed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2" , name = "GeolocationManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitGeolocationManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "error_message"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the error message" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_geolocation_manager_failed" webkit_geolocation_manager_failed :: 
    Ptr GeolocationManager ->               -- manager : TInterface (Name {namespace = "WebKit2", name = "GeolocationManager"})
    CString ->                              -- error_message : TBasicType TUTF8
    IO ()

-- | Notify /@manager@/ that determining the position failed.
-- 
-- /Since: 2.26/
geolocationManagerFailed ::
    (B.CallStack.HasCallStack, MonadIO m, IsGeolocationManager a) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit2.Objects.GeolocationManager.GeolocationManager'
    -> T.Text
    -- ^ /@errorMessage@/: the error message
    -> m ()
geolocationManagerFailed :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGeolocationManager a) =>
a -> Text -> m ()
geolocationManagerFailed a
manager Text
errorMessage = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GeolocationManager
manager' <- a -> IO (Ptr GeolocationManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CString
errorMessage' <- Text -> IO CString
textToCString Text
errorMessage
    Ptr GeolocationManager -> CString -> IO ()
webkit_geolocation_manager_failed Ptr GeolocationManager
manager' CString
errorMessage'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
errorMessage'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GeolocationManagerFailedMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsGeolocationManager a) => O.OverloadedMethod GeolocationManagerFailedMethodInfo a signature where
    overloadedMethod = geolocationManagerFailed

instance O.OverloadedMethodInfo GeolocationManagerFailedMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2.Objects.GeolocationManager.geolocationManagerFailed",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.27/docs/GI-WebKit2-Objects-GeolocationManager.html#v:geolocationManagerFailed"
        }


#endif

-- method GeolocationManager::get_enable_high_accuracy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2" , name = "GeolocationManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitGeolocationManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_geolocation_manager_get_enable_high_accuracy" webkit_geolocation_manager_get_enable_high_accuracy :: 
    Ptr GeolocationManager ->               -- manager : TInterface (Name {namespace = "WebKit2", name = "GeolocationManager"})
    IO CInt

-- | Get whether high accuracy is enabled.
-- 
-- /Since: 2.26/
geolocationManagerGetEnableHighAccuracy ::
    (B.CallStack.HasCallStack, MonadIO m, IsGeolocationManager a) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit2.Objects.GeolocationManager.GeolocationManager'
    -> m Bool
geolocationManagerGetEnableHighAccuracy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGeolocationManager a) =>
a -> m Bool
geolocationManagerGetEnableHighAccuracy a
manager = GeolocationManagerStartCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (GeolocationManagerStartCallback -> m Bool)
-> GeolocationManagerStartCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr GeolocationManager
manager' <- a -> IO (Ptr GeolocationManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CInt
result <- Ptr GeolocationManager -> IO CInt
webkit_geolocation_manager_get_enable_high_accuracy Ptr GeolocationManager
manager'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    Bool -> GeolocationManagerStartCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data GeolocationManagerGetEnableHighAccuracyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGeolocationManager a) => O.OverloadedMethod GeolocationManagerGetEnableHighAccuracyMethodInfo a signature where
    overloadedMethod = geolocationManagerGetEnableHighAccuracy

instance O.OverloadedMethodInfo GeolocationManagerGetEnableHighAccuracyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2.Objects.GeolocationManager.geolocationManagerGetEnableHighAccuracy",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.27/docs/GI-WebKit2-Objects-GeolocationManager.html#v:geolocationManagerGetEnableHighAccuracy"
        }


#endif

-- method GeolocationManager::update_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2" , name = "GeolocationManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitGeolocationManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "position"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2" , name = "GeolocationPosition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitGeolocationPosition"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_geolocation_manager_update_position" webkit_geolocation_manager_update_position :: 
    Ptr GeolocationManager ->               -- manager : TInterface (Name {namespace = "WebKit2", name = "GeolocationManager"})
    Ptr WebKit2.GeolocationPosition.GeolocationPosition -> -- position : TInterface (Name {namespace = "WebKit2", name = "GeolocationPosition"})
    IO ()

-- | Notify /@manager@/ that position has been updated to /@position@/.
-- 
-- /Since: 2.26/
geolocationManagerUpdatePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsGeolocationManager a) =>
    a
    -- ^ /@manager@/: a t'GI.WebKit2.Objects.GeolocationManager.GeolocationManager'
    -> WebKit2.GeolocationPosition.GeolocationPosition
    -- ^ /@position@/: a t'GI.WebKit2.Structs.GeolocationPosition.GeolocationPosition'
    -> m ()
geolocationManagerUpdatePosition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGeolocationManager a) =>
a -> GeolocationPosition -> m ()
geolocationManagerUpdatePosition a
manager GeolocationPosition
position = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GeolocationManager
manager' <- a -> IO (Ptr GeolocationManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr GeolocationPosition
position' <- GeolocationPosition -> IO (Ptr GeolocationPosition)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GeolocationPosition
position
    Ptr GeolocationManager -> Ptr GeolocationPosition -> IO ()
webkit_geolocation_manager_update_position Ptr GeolocationManager
manager' Ptr GeolocationPosition
position'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    GeolocationPosition -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GeolocationPosition
position
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GeolocationManagerUpdatePositionMethodInfo
instance (signature ~ (WebKit2.GeolocationPosition.GeolocationPosition -> m ()), MonadIO m, IsGeolocationManager a) => O.OverloadedMethod GeolocationManagerUpdatePositionMethodInfo a signature where
    overloadedMethod = geolocationManagerUpdatePosition

instance O.OverloadedMethodInfo GeolocationManagerUpdatePositionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2.Objects.GeolocationManager.geolocationManagerUpdatePosition",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.27/docs/GI-WebKit2-Objects-GeolocationManager.html#v:geolocationManagerUpdatePosition"
        }


#endif