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

Generated when the pointer enters or leaves a window.
-}

module GI.Gdk.Structs.EventCrossing
    ( 

-- * Exported types
    EventCrossing(..)                       ,
    newZeroEventCrossing                    ,
    noEventCrossing                         ,


 -- * Properties
-- ** detail #attr:detail#
    eventCrossing_detail                    ,
    getEventCrossingDetail                  ,
    setEventCrossingDetail                  ,


-- ** focus #attr:focus#
    eventCrossing_focus                     ,
    getEventCrossingFocus                   ,
    setEventCrossingFocus                   ,


-- ** mode #attr:mode#
    eventCrossing_mode                      ,
    getEventCrossingMode                    ,
    setEventCrossingMode                    ,


-- ** sendEvent #attr:sendEvent#
    eventCrossing_sendEvent                 ,
    getEventCrossingSendEvent               ,
    setEventCrossingSendEvent               ,


-- ** state #attr:state#
    eventCrossing_state                     ,
    getEventCrossingState                   ,
    setEventCrossingState                   ,


-- ** subwindow #attr:subwindow#
    clearEventCrossingSubwindow             ,
    eventCrossing_subwindow                 ,
    getEventCrossingSubwindow               ,
    setEventCrossingSubwindow               ,


-- ** time #attr:time#
    eventCrossing_time                      ,
    getEventCrossingTime                    ,
    setEventCrossingTime                    ,


-- ** type #attr:type#
    eventCrossing_type                      ,
    getEventCrossingType                    ,
    setEventCrossingType                    ,


-- ** window #attr:window#
    clearEventCrossingWindow                ,
    eventCrossing_window                    ,
    getEventCrossingWindow                  ,
    setEventCrossingWindow                  ,


-- ** x #attr:x#
    eventCrossing_x                         ,
    getEventCrossingX                       ,
    setEventCrossingX                       ,


-- ** xRoot #attr:xRoot#
    eventCrossing_xRoot                     ,
    getEventCrossingXRoot                   ,
    setEventCrossingXRoot                   ,


-- ** y #attr:y#
    eventCrossing_y                         ,
    getEventCrossingY                       ,
    setEventCrossingY                       ,


-- ** yRoot #attr:yRoot#
    eventCrossing_yRoot                     ,
    getEventCrossingYRoot                   ,
    setEventCrossingYRoot                   ,




    ) 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 {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window

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

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

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


noEventCrossing :: Maybe EventCrossing
noEventCrossing = Nothing

getEventCrossingType :: MonadIO m => EventCrossing -> m Gdk.Enums.EventType
getEventCrossingType s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

setEventCrossingType :: MonadIO m => EventCrossing -> Gdk.Enums.EventType -> m ()
setEventCrossingType s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CUInt)

data EventCrossingTypeFieldInfo
instance AttrInfo EventCrossingTypeFieldInfo where
    type AttrAllowedOps EventCrossingTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingTypeFieldInfo = (~) Gdk.Enums.EventType
    type AttrBaseTypeConstraint EventCrossingTypeFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingTypeFieldInfo = Gdk.Enums.EventType
    type AttrLabel EventCrossingTypeFieldInfo = "type"
    type AttrOrigin EventCrossingTypeFieldInfo = EventCrossing
    attrGet _ = getEventCrossingType
    attrSet _ = setEventCrossingType
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_type :: AttrLabelProxy "type"
eventCrossing_type = AttrLabelProxy


getEventCrossingWindow :: MonadIO m => EventCrossing -> m (Maybe Gdk.Window.Window)
getEventCrossingWindow s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (Ptr Gdk.Window.Window)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newObject Gdk.Window.Window) val'
        return val''
    return result

setEventCrossingWindow :: MonadIO m => EventCrossing -> Ptr Gdk.Window.Window -> m ()
setEventCrossingWindow s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: Ptr Gdk.Window.Window)

clearEventCrossingWindow :: MonadIO m => EventCrossing -> m ()
clearEventCrossingWindow s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)

data EventCrossingWindowFieldInfo
instance AttrInfo EventCrossingWindowFieldInfo where
    type AttrAllowedOps EventCrossingWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventCrossingWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrBaseTypeConstraint EventCrossingWindowFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventCrossingWindowFieldInfo = "window"
    type AttrOrigin EventCrossingWindowFieldInfo = EventCrossing
    attrGet _ = getEventCrossingWindow
    attrSet _ = setEventCrossingWindow
    attrConstruct = undefined
    attrClear _ = clearEventCrossingWindow

eventCrossing_window :: AttrLabelProxy "window"
eventCrossing_window = AttrLabelProxy


getEventCrossingSendEvent :: MonadIO m => EventCrossing -> m Int8
getEventCrossingSendEvent s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO Int8
    return val

setEventCrossingSendEvent :: MonadIO m => EventCrossing -> Int8 -> m ()
setEventCrossingSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Int8)

data EventCrossingSendEventFieldInfo
instance AttrInfo EventCrossingSendEventFieldInfo where
    type AttrAllowedOps EventCrossingSendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingSendEventFieldInfo = (~) Int8
    type AttrBaseTypeConstraint EventCrossingSendEventFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingSendEventFieldInfo = Int8
    type AttrLabel EventCrossingSendEventFieldInfo = "send_event"
    type AttrOrigin EventCrossingSendEventFieldInfo = EventCrossing
    attrGet _ = getEventCrossingSendEvent
    attrSet _ = setEventCrossingSendEvent
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_sendEvent :: AttrLabelProxy "sendEvent"
eventCrossing_sendEvent = AttrLabelProxy


getEventCrossingSubwindow :: MonadIO m => EventCrossing -> m (Maybe Gdk.Window.Window)
getEventCrossingSubwindow s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO (Ptr Gdk.Window.Window)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newObject Gdk.Window.Window) val'
        return val''
    return result

setEventCrossingSubwindow :: MonadIO m => EventCrossing -> Ptr Gdk.Window.Window -> m ()
setEventCrossingSubwindow s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: Ptr Gdk.Window.Window)

clearEventCrossingSubwindow :: MonadIO m => EventCrossing -> m ()
clearEventCrossingSubwindow s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (FP.nullPtr :: Ptr Gdk.Window.Window)

data EventCrossingSubwindowFieldInfo
instance AttrInfo EventCrossingSubwindowFieldInfo where
    type AttrAllowedOps EventCrossingSubwindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventCrossingSubwindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrBaseTypeConstraint EventCrossingSubwindowFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingSubwindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventCrossingSubwindowFieldInfo = "subwindow"
    type AttrOrigin EventCrossingSubwindowFieldInfo = EventCrossing
    attrGet _ = getEventCrossingSubwindow
    attrSet _ = setEventCrossingSubwindow
    attrConstruct = undefined
    attrClear _ = clearEventCrossingSubwindow

eventCrossing_subwindow :: AttrLabelProxy "subwindow"
eventCrossing_subwindow = AttrLabelProxy


getEventCrossingTime :: MonadIO m => EventCrossing -> m Word32
getEventCrossingTime s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO Word32
    return val

setEventCrossingTime :: MonadIO m => EventCrossing -> Word32 -> m ()
setEventCrossingTime s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: Word32)

data EventCrossingTimeFieldInfo
instance AttrInfo EventCrossingTimeFieldInfo where
    type AttrAllowedOps EventCrossingTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingTimeFieldInfo = (~) Word32
    type AttrBaseTypeConstraint EventCrossingTimeFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingTimeFieldInfo = Word32
    type AttrLabel EventCrossingTimeFieldInfo = "time"
    type AttrOrigin EventCrossingTimeFieldInfo = EventCrossing
    attrGet _ = getEventCrossingTime
    attrSet _ = setEventCrossingTime
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_time :: AttrLabelProxy "time"
eventCrossing_time = AttrLabelProxy


getEventCrossingX :: MonadIO m => EventCrossing -> m Double
getEventCrossingX s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO CDouble
    let val' = realToFrac val
    return val'

setEventCrossingX :: MonadIO m => EventCrossing -> Double -> m ()
setEventCrossingX s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = realToFrac val
    poke (ptr `plusPtr` 40) (val' :: CDouble)

data EventCrossingXFieldInfo
instance AttrInfo EventCrossingXFieldInfo where
    type AttrAllowedOps EventCrossingXFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingXFieldInfo = (~) Double
    type AttrBaseTypeConstraint EventCrossingXFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingXFieldInfo = Double
    type AttrLabel EventCrossingXFieldInfo = "x"
    type AttrOrigin EventCrossingXFieldInfo = EventCrossing
    attrGet _ = getEventCrossingX
    attrSet _ = setEventCrossingX
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_x :: AttrLabelProxy "x"
eventCrossing_x = AttrLabelProxy


getEventCrossingY :: MonadIO m => EventCrossing -> m Double
getEventCrossingY s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 48) :: IO CDouble
    let val' = realToFrac val
    return val'

setEventCrossingY :: MonadIO m => EventCrossing -> Double -> m ()
setEventCrossingY s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = realToFrac val
    poke (ptr `plusPtr` 48) (val' :: CDouble)

data EventCrossingYFieldInfo
instance AttrInfo EventCrossingYFieldInfo where
    type AttrAllowedOps EventCrossingYFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingYFieldInfo = (~) Double
    type AttrBaseTypeConstraint EventCrossingYFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingYFieldInfo = Double
    type AttrLabel EventCrossingYFieldInfo = "y"
    type AttrOrigin EventCrossingYFieldInfo = EventCrossing
    attrGet _ = getEventCrossingY
    attrSet _ = setEventCrossingY
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_y :: AttrLabelProxy "y"
eventCrossing_y = AttrLabelProxy


getEventCrossingXRoot :: MonadIO m => EventCrossing -> m Double
getEventCrossingXRoot s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 56) :: IO CDouble
    let val' = realToFrac val
    return val'

setEventCrossingXRoot :: MonadIO m => EventCrossing -> Double -> m ()
setEventCrossingXRoot s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = realToFrac val
    poke (ptr `plusPtr` 56) (val' :: CDouble)

data EventCrossingXRootFieldInfo
instance AttrInfo EventCrossingXRootFieldInfo where
    type AttrAllowedOps EventCrossingXRootFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingXRootFieldInfo = (~) Double
    type AttrBaseTypeConstraint EventCrossingXRootFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingXRootFieldInfo = Double
    type AttrLabel EventCrossingXRootFieldInfo = "x_root"
    type AttrOrigin EventCrossingXRootFieldInfo = EventCrossing
    attrGet _ = getEventCrossingXRoot
    attrSet _ = setEventCrossingXRoot
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_xRoot :: AttrLabelProxy "xRoot"
eventCrossing_xRoot = AttrLabelProxy


getEventCrossingYRoot :: MonadIO m => EventCrossing -> m Double
getEventCrossingYRoot s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 64) :: IO CDouble
    let val' = realToFrac val
    return val'

setEventCrossingYRoot :: MonadIO m => EventCrossing -> Double -> m ()
setEventCrossingYRoot s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = realToFrac val
    poke (ptr `plusPtr` 64) (val' :: CDouble)

data EventCrossingYRootFieldInfo
instance AttrInfo EventCrossingYRootFieldInfo where
    type AttrAllowedOps EventCrossingYRootFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingYRootFieldInfo = (~) Double
    type AttrBaseTypeConstraint EventCrossingYRootFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingYRootFieldInfo = Double
    type AttrLabel EventCrossingYRootFieldInfo = "y_root"
    type AttrOrigin EventCrossingYRootFieldInfo = EventCrossing
    attrGet _ = getEventCrossingYRoot
    attrSet _ = setEventCrossingYRoot
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_yRoot :: AttrLabelProxy "yRoot"
eventCrossing_yRoot = AttrLabelProxy


getEventCrossingMode :: MonadIO m => EventCrossing -> m Gdk.Enums.CrossingMode
getEventCrossingMode s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 72) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

setEventCrossingMode :: MonadIO m => EventCrossing -> Gdk.Enums.CrossingMode -> m ()
setEventCrossingMode s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 72) (val' :: CUInt)

data EventCrossingModeFieldInfo
instance AttrInfo EventCrossingModeFieldInfo where
    type AttrAllowedOps EventCrossingModeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingModeFieldInfo = (~) Gdk.Enums.CrossingMode
    type AttrBaseTypeConstraint EventCrossingModeFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingModeFieldInfo = Gdk.Enums.CrossingMode
    type AttrLabel EventCrossingModeFieldInfo = "mode"
    type AttrOrigin EventCrossingModeFieldInfo = EventCrossing
    attrGet _ = getEventCrossingMode
    attrSet _ = setEventCrossingMode
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_mode :: AttrLabelProxy "mode"
eventCrossing_mode = AttrLabelProxy


getEventCrossingDetail :: MonadIO m => EventCrossing -> m Gdk.Enums.NotifyType
getEventCrossingDetail s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 76) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

setEventCrossingDetail :: MonadIO m => EventCrossing -> Gdk.Enums.NotifyType -> m ()
setEventCrossingDetail s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 76) (val' :: CUInt)

data EventCrossingDetailFieldInfo
instance AttrInfo EventCrossingDetailFieldInfo where
    type AttrAllowedOps EventCrossingDetailFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingDetailFieldInfo = (~) Gdk.Enums.NotifyType
    type AttrBaseTypeConstraint EventCrossingDetailFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingDetailFieldInfo = Gdk.Enums.NotifyType
    type AttrLabel EventCrossingDetailFieldInfo = "detail"
    type AttrOrigin EventCrossingDetailFieldInfo = EventCrossing
    attrGet _ = getEventCrossingDetail
    attrSet _ = setEventCrossingDetail
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_detail :: AttrLabelProxy "detail"
eventCrossing_detail = AttrLabelProxy


getEventCrossingFocus :: MonadIO m => EventCrossing -> m Bool
getEventCrossingFocus s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 80) :: IO CInt
    let val' = (/= 0) val
    return val'

setEventCrossingFocus :: MonadIO m => EventCrossing -> Bool -> m ()
setEventCrossingFocus s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 80) (val' :: CInt)

data EventCrossingFocusFieldInfo
instance AttrInfo EventCrossingFocusFieldInfo where
    type AttrAllowedOps EventCrossingFocusFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingFocusFieldInfo = (~) Bool
    type AttrBaseTypeConstraint EventCrossingFocusFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingFocusFieldInfo = Bool
    type AttrLabel EventCrossingFocusFieldInfo = "focus"
    type AttrOrigin EventCrossingFocusFieldInfo = EventCrossing
    attrGet _ = getEventCrossingFocus
    attrSet _ = setEventCrossingFocus
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_focus :: AttrLabelProxy "focus"
eventCrossing_focus = AttrLabelProxy


getEventCrossingState :: MonadIO m => EventCrossing -> m [Gdk.Flags.ModifierType]
getEventCrossingState s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 84) :: IO CUInt
    let val' = wordToGFlags val
    return val'

setEventCrossingState :: MonadIO m => EventCrossing -> [Gdk.Flags.ModifierType] -> m ()
setEventCrossingState s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = gflagsToWord val
    poke (ptr `plusPtr` 84) (val' :: CUInt)

data EventCrossingStateFieldInfo
instance AttrInfo EventCrossingStateFieldInfo where
    type AttrAllowedOps EventCrossingStateFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingStateFieldInfo = (~) [Gdk.Flags.ModifierType]
    type AttrBaseTypeConstraint EventCrossingStateFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingStateFieldInfo = [Gdk.Flags.ModifierType]
    type AttrLabel EventCrossingStateFieldInfo = "state"
    type AttrOrigin EventCrossingStateFieldInfo = EventCrossing
    attrGet _ = getEventCrossingState
    attrSet _ = setEventCrossingState
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_state :: AttrLabelProxy "state"
eventCrossing_state = AttrLabelProxy



instance O.HasAttributeList EventCrossing
type instance O.AttributeList EventCrossing = EventCrossingAttributeList
type EventCrossingAttributeList = ('[ '("type", EventCrossingTypeFieldInfo), '("window", EventCrossingWindowFieldInfo), '("sendEvent", EventCrossingSendEventFieldInfo), '("subwindow", EventCrossingSubwindowFieldInfo), '("time", EventCrossingTimeFieldInfo), '("x", EventCrossingXFieldInfo), '("y", EventCrossingYFieldInfo), '("xRoot", EventCrossingXRootFieldInfo), '("yRoot", EventCrossingYRootFieldInfo), '("mode", EventCrossingModeFieldInfo), '("detail", EventCrossingDetailFieldInfo), '("focus", EventCrossingFocusFieldInfo), '("state", EventCrossingStateFieldInfo)] :: [(Symbol, *)])

type family ResolveEventCrossingMethod (t :: Symbol) (o :: *) :: * where
    ResolveEventCrossingMethod l o = O.MethodResolutionFailed l o

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

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