-- This file is part of Qtah.
--
-- Copyright 2015-2021 The Qtah Authors.
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU Lesser General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-- GNU Lesser General Public License for more details.
--
-- You should have received a copy of the GNU Lesser General Public License
-- along with this program.  If not, see <http://www.gnu.org/licenses/>.

module Graphics.UI.Qtah.Generator.Interface.Widgets.QGraphicsItem (
  aModule,
  c_QGraphicsItem,
  e_CacheMode,
  e_GraphicsItemChange,
  e_PanelModality,
  fl_GraphicsItemFlags,
  ) where

import Foreign.Hoppy.Generator.Spec (
  addReqIncludes,
  classSetEntityPrefix,
  ident,
  ident1,
  includeStd,
  makeClass,
  mkConstMethod,
  mkConstMethod',
  mkMethod,
  mkMethod',
  mkProp,
  np,
  )
import Foreign.Hoppy.Generator.Types (voidT, objT, ptrT, boolT, constT, intT)
import Foreign.Hoppy.Generator.Version (collect, just, test)
import Graphics.UI.Qtah.Generator.Config (qtVersion)
import Graphics.UI.Qtah.Generator.Interface.Core.Types (qreal)
import Graphics.UI.Qtah.Generator.Interface.Core.QPointF (c_QPointF)
import Graphics.UI.Qtah.Generator.Interface.Core.QRectF (c_QRectF)
import Graphics.UI.Qtah.Generator.Interface.Core.QString (c_QString)
import Graphics.UI.Qtah.Generator.Interface.Gui.QCursor (c_QCursor)
-- import Graphics.UI.Qtah.Generator.Interface.Gui.QPolygonF (c_QPolygonF)
import Graphics.UI.Qtah.Generator.Interface.Gui.QPainterPath (c_QPainterPath)
-- import Graphics.UI.Qtah.Generator.Interface.Gui.QTransform (c_QTransform)
import {-# SOURCE #-} Graphics.UI.Qtah.Generator.Interface.Widgets.QGraphicsScene (c_QGraphicsScene)
import Graphics.UI.Qtah.Generator.Module (AModule (AQtModule), makeQtModule)
import Graphics.UI.Qtah.Generator.Types

{-# ANN module "HLint: ignore Use camelCase" #-}

aModule :: AModule
aModule =
  QtModule -> AModule
AQtModule (QtModule -> AModule) -> QtModule -> AModule
forall a b. (a -> b) -> a -> b
$
  [String] -> [QtExport] -> QtModule
makeQtModule [String
"Widgets", String
"QGraphicsItem"]
  [ Class -> QtExport
forall a. Exportable a => a -> QtExport
qtExport Class
c_QGraphicsItem
  , CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_CacheMode
  , CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_GraphicsItemChange
  , CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_GraphicsItemFlag
  , Flags -> QtExport
forall a. Exportable a => a -> QtExport
qtExport Flags
fl_GraphicsItemFlags
  , CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_PanelModality
  ]

c_QGraphicsItem :: Class
c_QGraphicsItem =
  [Include] -> Class -> Class
forall a. HasReqs a => [Include] -> a -> a
addReqIncludes [String -> Include
includeStd String
"QGraphicsItem"] (Class -> Class) -> Class -> Class
forall a b. (a -> b) -> a -> b
$
  String -> Class -> Class
classSetEntityPrefix String
"" (Class -> Class) -> Class -> Class
forall a b. (a -> b) -> a -> b
$
  Identifier -> Maybe ExtName -> [Class] -> [ClassEntity] -> Class
makeClass (String -> Identifier
ident String
"QGraphicsItem") Maybe ExtName
forall a. Maybe a
Nothing []
  [ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"acceptDrops" [Parameter]
np Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"acceptHoverEvents" [Parameter]
np Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"acceptTouchEvents" [Parameter]
np Type
boolT
  -- TODO mkConstMethod "acceptedMouseButtons" np $ objT c_Qt::MouseButtons
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"advance" [Type
intT] Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"boundingRect" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QRectF
  -- TODO mkConstMethod "boundingRegion" [objT c_QTransform] $ objT c_QRegion
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"boundingRegionGranularity" [Parameter]
np Type
qreal
  -- TODO mkConstMethod "cacheMode" np $ enumT e_CacheMode
  -- TODO mkConstMethod "childItems" np $ objT c_QList<QGraphicsItem $ objT c_*>
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"childrenBoundingRect" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QRectF
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"clearFocus" [Parameter]
np Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"clipPath" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPainterPath
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"collidesWithItem" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
constT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] Type
boolT
  -- TODO mkConstMethod' "collidesWithItem" "collidesWithItemAll"
  --   [ptrT $ constT $ objT c_QGraphicsItem, objT c_Qt::ItemSelectionMode] boolT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"collidesWithPath" [Class -> Type
objT Class
c_QPainterPath] Type
boolT
  -- TODO mkConstMethod' "collidesWithPath" "collidesWithPathAll"
  --   [objT c_QPainterPath, objT c_Qt::ItemSelectionMode] boolT
  -- TODO mkConstMethod "collidingItems" np $ objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod' "collidingItems" "collidingItemsAll"
  --   [objT c_Qt::ItemSelectionMode] $ objT c_QList<QGraphicsItem $ objT c_*>
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"commonAncestorItem" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
constT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$
      Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"contains" [Class -> Type
objT Class
c_QPointF] Type
boolT
  , String -> Type -> ClassEntity
mkProp String
"cursor" (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QCursor
  -- TODO mkConstMethod "data" [intT] $ objT c_QVariant
  -- TODO mkConstMethod "deviceTransform" [objT c_QTransform] $ objT c_QTransform
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"effectiveOpacity" [Parameter]
np Type
qreal
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"ensureVisible" [Parameter]
np Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"ensureVisible" String
"ensureVisibleRectFAll" [Class -> Type
objT Class
c_QRectF, Type
intT, Type
intT] Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"ensureVisible" String
"ensureVisibleRaw"
      [Type
qreal, Type
qreal, Type
qreal, Type
qreal] Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"ensureVisible" String
"ensureVisibleRawAll"
      [Type
qreal, Type
qreal, Type
qreal, Type
qreal, Type
intT, Type
intT] Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"filtersChildEvents" [Parameter]
np Type
boolT
  -- TODO mkConstMethod "flags" np $ objT c_GraphicsItemFlags
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"focusItem" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"focusProxy" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"grabKeyboard" [Parameter]
np Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"grabMouse" [Parameter]
np Type
voidT
  -- TODO mkConstMethod "graphicsEffect" np $ ptrT $ objT c_QGraphicsEffect
  -- TODO mkConstMethod "group" np $ ptrT $ objT c_QGraphicsItemGroup
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"hasCursor" [Parameter]
np Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"hasFocus" [Parameter]
np Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"hide" [Parameter]
np Type
voidT
  -- TODO mkConstMethod "inputMethodHints" np $ objT c_Qt::InputMethodHints
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"installSceneEventFilter" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isActive" [Parameter]
np Type
boolT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isAncestorOf" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
constT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isBlockedByModalPanel" [Parameter]
np Type
boolT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"isBlockedByModalPanel" String
"isBlockedByModalPanelAll"
      [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isClipped" [Parameter]
np Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isEnabled" [Parameter]
np Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isObscured" [Parameter]
np Type
boolT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"isObscured" String
"isObscuredRaw" [Type
qreal, Type
qreal, Type
qreal, Type
qreal] Type
boolT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"isObscured" String
"isObscuredRectF" [Class -> Type
objT Class
c_QRectF] Type
boolT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isObscuredBy" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
constT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isPanel" [Parameter]
np Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isSelected" [Parameter]
np Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isUnderMouse" [Parameter]
np Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isVisible" [Parameter]
np Type
boolT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isVisibleTo" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
constT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isWidget" [Parameter]
np Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isWindow" [Parameter]
np Type
boolT
  -- TODO mkConstMethod "itemTransform" [ptrT $ constT $ objT c_QGraphicsItem] $
  --   objT c_QTransform
  -- TODO mkConstMethod' "itemTransform" "itemTransformAll"
  --   [ptrT $ constT $ objT c_QGraphicsItem, ptrT $ boolT] $ objT c_QTransform
  -- TODO mkConstMethod' "mapFromItem" "mapFromItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, objT c_QPointF] $ objT c_QPointF
  -- TODO mkConstMethod' "mapFromItem" "mapFromItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, objT c_QRectF] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapFromItem" "mapFromItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, objT c_QPolygonF] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapFromItem" "mapFromItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, objT c_QPainterPath] $ objT c_QPainterPath
  -- TODO mkConstMethod' "mapFromItem" "mapFromItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, qreal, qreal, qreal, qreal] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapFromItem" "mapFromItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, qreal, qreal] $ objT c_QPointF
  -- TODO mkConstMethod' "mapFromParent" "mapFromParent"
  --   [objT c_QPointF] $ objT c_QPointF
  -- TODO mkConstMethod' "mapFromParent" "mapFromParent"
  --   [objT c_QRectF] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapFromParent" "mapFromParent"
  --   [objT c_QPolygonF] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapFromParent" "mapFromParent"
  --   [objT c_QPainterPath] $ objT c_QPainterPath
  -- TODO mkConstMethod' "mapFromParent" "mapFromParent"
  --   [qreal, qreal, qreal, qreal] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapFromParent" "mapFromParent"
  --   [qreal, qreal] $ objT c_QPointF
  -- TODO mkConstMethod' "mapFromScene" "mapFromScene"
  --   [objT c_QPointF] $ objT c_QPointF
  -- TODO mkConstMethod' "mapFromScene" "mapFromScene"
  --   [objT c_QRectF] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapFromScene" "mapFromScene"
  --   [objT c_QPolygonF] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapFromScene" "mapFromScene"
  --   [objT c_QPainterPath] $ objT c_QPainterPath
  -- TODO mkConstMethod' "mapFromScene" "mapFromScene"
  --   [qreal, qreal, qreal, qreal] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapFromScene" "mapFromScene"
  --   [qreal, qreal] $ objT c_QPointF
  -- TODO mkConstMethod' "mapRectFromItem" "mapRectFromItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, objT c_QRectF] $ objT c_QRectF
  -- TODO mkConstMethod' "mapRectFromItem" "mapRectFromItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, qreal, qreal, qreal, qreal] $ objT c_QRectF
  -- TODO mkConstMethod' "mapRectFromParent" "mapRectFromParent"
  --   [objT c_QRectF] $ objT c_QRectF
  -- TODO mkConstMethod' "mapRectFromParent" "mapRectFromParent"
  --   [qreal, qreal, qreal, qreal] $ objT c_QRectF
  -- TODO mkConstMethod' "mapRectFromScene" "mapRectFromScene"
  --   [objT c_QRectF] $ objT c_QRectF
  -- TODO mkConstMethod' "mapRectFromScene" "mapRectFromScene"
  --   [qreal, qreal, qreal, qreal] $ objT c_QRectF
  -- TODO mkConstMethod' "mapRectToItem" "mapRectToItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, objT c_QRectF] $ objT c_QRectF
  -- TODO mkConstMethod' "mapRectToItem" "mapRectToItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, qreal, qreal, qreal, qreal] $ objT c_QRectF
  -- TODO mkConstMethod' "mapRectToParent" "mapRectToParent"
  --   [objT c_QRectF] $ objT c_QRectF
  -- TODO mkConstMethod' "mapRectToParent" "mapRectToParent"
  --   [qreal, qreal, qreal, qreal] $ objT c_QRectF
  -- TODO mkConstMethod' "mapRectToScene" "mapRectToScene"
  --   [objT c_QRectF] $ objT c_QRectF
  -- TODO mkConstMethod' "mapRectToScene" "mapRectToScene"
  --   [qreal, qreal, qreal, qreal] $ objT c_QRectF
  -- TODO mkConstMethod' "mapToItem" "mapToItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, objT c_QPointF] $ objT c_QPointF
  -- TODO mkConstMethod' "mapToItem" "mapToItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, objT c_QRectF] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapToItem" "mapToItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, objT c_QPolygonF] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapToItem" "mapToItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, objT c_QPainterPath] $ objT c_QPainterPath
  -- TODO mkConstMethod' "mapToItem" "mapToItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, qreal, qreal, qreal, qreal] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapToItem" "mapToItem"
  --   [ptrT $ constT $ objT c_QGraphicsItem, qreal, qreal] $ objT c_QPointF
  -- TODO mkConstMethod' "mapToParent" "mapToParent"
  --   [objT c_QPointF] $ objT c_QPointF
  -- TODO mkConstMethod' "mapToParent" "mapToParent"
  --   [objT c_QRectF] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapToParent" "mapToParent"
  --   [objT c_QPolygonF] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapToParent" "mapToParent"
  --   [objT c_QPainterPath] $ objT c_QPainterPath
  -- TODO mkConstMethod' "mapToParent" "mapToParent"
  --   [qreal, qreal, qreal, qreal] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapToParent" "mapToParent"
  --   [qreal, qreal] $ objT c_QPointF
  -- TODO mkConstMethod' "mapToScene" "mapToScene"
  --   [objT c_QPointF] $ objT c_QPointF
  -- TODO mkConstMethod' "mapToScene" "mapToScene"
  --   [objT c_QRectF] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapToScene" "mapToScene"
  --   [objT c_QPolygonF] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapToScene" "mapToScene"
  --   [objT c_QPainterPath] $ objT c_QPainterPath
  -- TODO mkConstMethod' "mapToScene" "mapToScene"
  --   [qreal, qreal, qreal, qreal] $ objT c_QPolygonF
  -- TODO mkConstMethod' "mapToScene" "mapToScene"
  --   [qreal, qreal] $ objT c_QPointF
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"moveBy" [Type
qreal, Type
qreal] Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"opacity" [Parameter]
np Type
qreal
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"opaqueArea" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPainterPath
  -- TODO mkMethod "paint"
  --   [ptrT $ objT c_QPainter, ptrT $ constT $ objT c_QStyleOptionGraphicsItem] voidT
  -- TODO mkMethod' "paint" "paintAll"
  --   [ ptrT $ objT c_QPainter
  --   , ptrT $ constT $ objT c_QStyleOptionGraphicsItem
  --   , ptrT $ objT c_QWidget
  --   ] voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"panel" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem
  -- TODO mkConstMethod "panelModality" np $ objT c_PanelModality
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"parentItem" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem
  -- TODO mkConstMethod "parentObject" np $ ptrT $ objT c_QGraphicsObject
  -- TODO mkConstMethod "parentWidget" np $ ptrT $ objT c_QGraphicsWidget
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"pos" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPointF
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"removeSceneEventFilter" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"resetTransform" [Parameter]
np Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"rotation" [Parameter]
np Type
qreal
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"scale" [Parameter]
np Type
qreal
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"scene" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsScene
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"sceneBoundingRect" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QRectF
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"scenePos" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPointF
  -- TODO mkConstMethod "sceneTransform" np $ objT c_QTransform
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"scroll" [Type
qreal, Type
qreal] Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"scroll" String
"scrollAll" [Type
qreal, Type
qreal, Class -> Type
objT Class
c_QRectF] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setAcceptDrops" [Type
boolT] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setAcceptHoverEvents" [Type
boolT] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setAcceptTouchEvents" [Type
boolT] Type
voidT
  -- TODO mkMethod "setAcceptedMouseButtons" [objT c_Qt::MouseButtons] voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setActive" [Type
boolT] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setBoundingRegionGranularity" [Type
qreal] Type
voidT
  -- TODO mkMethod "setCacheMode" [objT c_CacheMode] voidT
  -- TODO mkMethod' "setCacheMode" "setCacheModeAll" [objT c_CacheMode, objT c_QSize] voidT
  -- TODO mkMethod "setData" [intT, objT c_QVariant] voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setEnabled" [Type
boolT] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setFiltersChildEvents" [Type
boolT] Type
voidT
  -- TODO mkMethod "setFlag" [objT c_GraphicsItemFlag] voidT
  -- TODO mkMethod' "setFlag" "setFlagAll" [objT c_GraphicsItemFlag, boolT] voidT
  -- TODO mkMethod "setFlags" [objT c_GraphicsItemFlags] voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setFocus" [Parameter]
np Type
voidT
 --  , mkMethod' "setFocus" "setFocusAll" [objT c_Qt::FocusReason] voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setFocusProxy" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] Type
voidT
  -- TODO mkMethod "setGraphicsEffect" [ptrT $ objT c_QGraphicsEffect] voidT
  -- TODO mkMethod "setGroup" [ptrT $ objT c_QGraphicsItemGroup] voidT
  -- TODO mkMethod "setInputMethodHints" [objT c_Qt::InputMethodHints] voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setOpacity" [Type
qreal] Type
voidT
  -- TODO mkMethod "setPanelModality" [objT c_PanelModality] voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setParentItem" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"setPos" String
"setPosPointF" [Class -> Type
objT Class
c_QPointF] Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"setPos" String
"setPosRaw" [Type
qreal, Type
qreal] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setRotation" [Type
qreal] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setScale" [Type
qreal] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setSelected" [Type
boolT] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setToolTip" [Class -> Type
objT Class
c_QString] Type
voidT
  -- TODO mkMethod "setTransform" [objT c_QTransform] voidT
  -- TODO mkMethod' "setTransform" "setTransformAll" [objT c_QTransform, boolT] voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"setTransformOriginPoint" String
"setTransformOriginPointF" [Class -> Type
objT Class
c_QPointF] Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"setTransformOriginPoint" String
"setTransformOriginPointRaw" [Type
qreal, Type
qreal] Type
voidT
  -- TODO mkMethod "setTransformations" [objT c_QList<QGraphicsTransform] voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setVisible" [Type
boolT] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setX" [Type
qreal] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setY" [Type
qreal] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setZValue" [Type
qreal] Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"shape" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPainterPath
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"show" [Parameter]
np Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"stackBefore" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
constT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] Type
voidT
  -- TODO mkMethod' "toGraphicsObject" "toGraphicsObject" np $
  --   ptrT $ objT c_QGraphicsObject
  -- TODO mkConstMethod' "toGraphicsObject" "toGraphicsObject" np $
  --   ptrT $ constT $ objT c_QGraphicsObject
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"toolTip" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QString
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"topLevelItem" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem
  -- TODO mkConstMethod "topLevelWidget" np $ ptrT $ objT c_QGraphicsWidget
  -- TODO mkConstMethod "transform" np $ objT c_QTransform
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"transformOriginPoint" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPointF
  -- TODO mkConstMethod "transformations" np $ objT c_QList<QGraphicsTransform $ objT c_*>
  , String -> String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"type" String
"itemType" [Parameter]
np Type
intT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"ungrabKeyboard" [Parameter]
np Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"ungrabMouse" [Parameter]
np Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"unsetCursor" [Parameter]
np Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"update" [Parameter]
np Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"update" String
"updateRectF" [Class -> Type
objT Class
c_QRectF] Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"update" String
"updateRaw" [Type
qreal, Type
qreal, Type
qreal, Type
qreal] Type
voidT
  -- TODO mkConstMethod "window" np $ ptrT $ objT c_QGraphicsWidget
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"x" [Parameter]
np Type
qreal
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"y" [Parameter]
np Type
qreal
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"zValue" [Parameter]
np Type
qreal
  ]

e_CacheMode :: CppEnum
e_CacheMode =
  Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QGraphicsItem" String
"CacheMode") [String -> Include
includeStd String
"QGraphicsItem"]
  [ String
"NoCache"
  , String
"ItemCoordinateCache"
  , String
"DeviceCoordinateCache"
  ]

e_GraphicsItemChange :: CppEnum
e_GraphicsItemChange =
  Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QGraphicsItem" String
"GraphicsItemChange") [String -> Include
includeStd String
"QGraphicsItem"]
  [ String
"ItemEnabledChange"
  , String
"ItemEnabledHasChanged"
  , String
"ItemMatrixChange"
  , String
"ItemPositionChange"
  , String
"ItemPositionHasChanged"
  , String
"ItemTransformChange"
  , String
"ItemTransformHasChanged"
  , String
"ItemRotationChange"
  , String
"ItemRotationHasChanged"
  , String
"ItemScaleChange"
  , String
"ItemScaleHasChanged"
  , String
"ItemTransformOriginPointChange"
  , String
"ItemTransformOriginPointHasChanged"
  , String
"ItemSelectedChange"
  , String
"ItemSelectedHasChanged"
  , String
"ItemVisibleChange"
  , String
"ItemVisibleHasChanged"
  , String
"ItemParentChange"
  , String
"ItemParentHasChanged"
  , String
"ItemChildAddedChange"
  , String
"ItemChildRemovedChange"
  , String
"ItemSceneChange"
  , String
"ItemSceneHasChanged"
  , String
"ItemCursorChange"
  , String
"ItemCursorHasChanged"
  , String
"ItemToolTipChange"
  , String
"ItemToolTipHasChanged"
  , String
"ItemFlagsChange"
  , String
"ItemFlagsHaveChanged"
  , String
"ItemZValueChange"
  , String
"ItemZValueHasChanged"
  , String
"ItemOpacityChange"
  , String
"ItemOpacityHasChanged"
  , String
"ItemScenePositionHasChanged"
  ]

(CppEnum
e_GraphicsItemFlag, Flags
fl_GraphicsItemFlags) =
  Identifier -> String -> [Include] -> [String] -> (CppEnum, Flags)
makeQtEnumAndFlags (String -> String -> Identifier
ident1 String
"QGraphicsItem" String
"GraphicsItemFlag") String
"GraphicsItemFlags"
    [String -> Include
includeStd String
"QGraphicsItem"] ([String] -> (CppEnum, Flags)) -> [String] -> (CppEnum, Flags)
forall a b. (a -> b) -> a -> b
$
  [Filtered String] -> [String]
forall a. [Filtered a] -> [a]
collect
  [ String -> Filtered String
forall a. a -> Filtered a
just String
"ItemIsMovable"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemIsSelectable"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemIsFocusable"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemClipsToShape"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemClipsChildrenToShape"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemIgnoresTransformations"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemIgnoresParentOpacity"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemDoesntPropagateOpacityToChildren"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemStacksBehindParent"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemUsesExtendedStyleOption"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemHasNoContents"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemSendsGeometryChanges"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemAcceptsInputMethod"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemNegativeZStacksBehindParent"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemIsPanel"
  , String -> Filtered String
forall a. a -> Filtered a
just String
"ItemSendsScenePositionChanges"
  , Bool -> String -> Filtered String
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
4]) String
"ItemContainsChildrenInShape"
  ]

e_PanelModality :: CppEnum
e_PanelModality =
  Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QGraphicsItem" String
"PanelModality") [String -> Include
includeStd String
"QGraphicsItem"]
  [ String
"NonModal"
  , String
"PanelModal"
  , String
"SceneModal"
  ]