-- 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.QGraphicsScene (
  aModule,
  c_QGraphicsScene,
  e_ItemIndexMethod,
  e_SceneLayer,
  fl_SceneLayers,
  ) where

import Foreign.Hoppy.Generator.Spec (
  addReqIncludes,
  classSetEntityPrefix,
  ident,
  ident1,
  includeStd,
  makeClass,
  mkMethod,
  mkMethod',
  mkCtor,
  mkConstMethod,
  mkConstMethod',
  mkProp,
  np,
  )
import Foreign.Hoppy.Generator.Types (voidT, objT, ptrT, intT, boolT, enumT)
import Foreign.Hoppy.Generator.Version (collect, just, test)
import Graphics.UI.Qtah.Generator.Config (qtVersion)
import Graphics.UI.Qtah.Generator.Interface.Core.Types (e_FocusReason, qreal)
import Graphics.UI.Qtah.Generator.Interface.Core.QEvent (c_QEvent)
-- import Graphics.UI.Qtah.Generator.Interface.Core.QLineF (c_QLineF)
import Graphics.UI.Qtah.Generator.Interface.Core.QObject (c_QObject)
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.QBrush (c_QBrush)
import Graphics.UI.Qtah.Generator.Interface.Gui.QFont (c_QFont)
import Graphics.UI.Qtah.Generator.Interface.Gui.QPainterPath (c_QPainterPath)
import Graphics.UI.Qtah.Generator.Interface.Gui.QPen (c_QPen)
import Graphics.UI.Qtah.Generator.Interface.Gui.QPolygonF (c_QPolygonF)
import Graphics.UI.Qtah.Generator.Interface.Gui.QTransform (c_QTransform)
import Graphics.UI.Qtah.Generator.Interface.Widgets.QGraphicsEllipseItem (c_QGraphicsEllipseItem)
import Graphics.UI.Qtah.Generator.Interface.Widgets.QGraphicsItem (c_QGraphicsItem)
import Graphics.UI.Qtah.Generator.Interface.Widgets.QGraphicsPolygonItem (c_QGraphicsPolygonItem)
import Graphics.UI.Qtah.Generator.Interface.Widgets.QGraphicsRectItem (c_QGraphicsRectItem)
-- import Graphics.UI.Qtah.Generator.Interface.Widgets.QWidget (c_QWidget)
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
"QGraphicsScene"] ([QtExport] -> QtModule) -> [QtExport] -> QtModule
forall a b. (a -> b) -> a -> b
$
  [ Class -> QtExport
forall a. Exportable a => a -> QtExport
qtExport Class
c_QGraphicsScene
  , CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_ItemIndexMethod
  , CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_SceneLayer
  , Flags -> QtExport
forall a. Exportable a => a -> QtExport
qtExport Flags
fl_SceneLayers
  ]

-- Due to a parsing bug types of the form `T<S*>` were generated incorrectly.
c_QGraphicsScene :: Class
c_QGraphicsScene =
  [Include] -> Class -> Class
forall a. HasReqs a => [Include] -> a -> a
addReqIncludes [String -> Include
includeStd String
"QGraphicsScene"] (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
"QGraphicsScene") Maybe ExtName
forall a. Maybe a
Nothing [Class
c_QObject] ([ClassEntity] -> Class) -> [ClassEntity] -> Class
forall a b. (a -> b) -> a -> b
$
  [Filtered ClassEntity] -> [ClassEntity]
forall a. [Filtered a] -> [a]
collect
  [ ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> ClassEntity
forall p. IsParameter p => String -> [p] -> ClassEntity
mkCtor String
"new" [Parameter]
np
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> ClassEntity
forall p. IsParameter p => String -> [p] -> ClassEntity
mkCtor String
"newWithParent" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QObject]
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> ClassEntity
forall p. IsParameter p => String -> [p] -> ClassEntity
mkCtor String
"newWithRect" [Class -> Type
objT Class
c_QRectF]
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> ClassEntity
forall p. IsParameter p => String -> [p] -> ClassEntity
mkCtor String
"newWithRaw" [Type
qreal, Type
qreal, Type
qreal, Type
qreal]
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"activePanel" [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 "activeWindow" np $ ptrT $ objT c_QGraphicsWidget
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"addEllipse" String
"addEllipseRectF"
      [Class -> Type
objT Class
c_QRectF] (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_QGraphicsEllipseItem
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"addEllipse" String
"addEllipseRectFAll"
      [Class -> Type
objT Class
c_QRectF, Class -> Type
objT Class
c_QPen, Class -> Type
objT Class
c_QBrush] (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_QGraphicsEllipseItem
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"addEllipse" String
"addEllipseRaw"
      [Type
qreal, Type
qreal, Type
qreal, Type
qreal] (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_QGraphicsEllipseItem
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"addEllipse" String
"addEllipseRawAll"
      [Type
qreal, Type
qreal, Type
qreal, Type
qreal, Class -> Type
objT Class
c_QPen, Class -> Type
objT Class
c_QBrush] (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_QGraphicsEllipseItem
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"addItem" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] Type
voidT
  -- TODO mkMethod' "addLine" "addLine" [objT c_QLineF] $
  --   ptrT $ objT c_QGraphicsLineItem
  -- TODO mkMethod' "addLine" "addLineAll" [objT c_QLineF, objT c_QPen] $
  --   ptrT $ objT c_QGraphicsLineItem
  -- TODO mkMethod' "addLine" "addLine" [qreal, qreal, qreal, qreal] $
  --   ptrT $ objT c_QGraphicsLineItem
  -- TODO mkMethod' "addLine" "addLineAll" [qreal, qreal, qreal, qreal, objT c_QPen] $
  --   ptrT $ objT c_QGraphicsLineItem
  -- TODO mkMethod "addPath" [objT c_QPainterPath] $ ptrT $ objT c_QGraphicsPathItem
  -- TODO mkMethod' "addPath" "addPathAll" [objT c_QPainterPath, objT c_QPen, objT c_QBrush] $
  --   ptrT $ objT c_QGraphicsPathItem
  -- TODO mkMethod "addPixmap" [objT c_QPixmap] $ ptrT $ objT c_QGraphicsPixmapItem
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"addPolygon" [Class -> Type
objT Class
c_QPolygonF] (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_QGraphicsPolygonItem
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"addPolygon" String
"addPolygonAll" [Class -> Type
objT Class
c_QPolygonF, Class -> Type
objT Class
c_QPen, Class -> Type
objT Class
c_QBrush] (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_QGraphicsPolygonItem
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"addRect" [Class -> Type
objT Class
c_QRectF] (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_QGraphicsRectItem
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"addRect" String
"addRectAll" [Class -> Type
objT Class
c_QRectF, Class -> Type
objT Class
c_QPen, Class -> Type
objT Class
c_QBrush] (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_QGraphicsRectItem
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"addRect" String
"addRectRaw" [Type
qreal, Type
qreal, Type
qreal, Type
qreal] (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_QGraphicsRectItem
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"addRect" String
"addRectRawAll"
      [Type
qreal, Type
qreal, Type
qreal, Type
qreal, Class -> Type
objT Class
c_QPen, Class -> Type
objT Class
c_QBrush] (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_QGraphicsRectItem
  -- TODO mkMethod "addSimpleText" [objT c_QString] $ ptrT $ objT c_QGraphicsSimpleTextItem
  -- TODO mkMethod' "addSimpleText" "addSimpleTextAll" [objT c_QString, objT c_QFont] $
  --   ptrT $ objT c_QGraphicsSimpleTextItem
  -- TODO mkMethod "addText" [objT c_QString] $ ptrT $ objT c_QGraphicsTextItem
  -- TODO mkMethod' "addText" "addTextAll" [objT c_QString, objT c_QFont] $
  --   ptrT $ objT c_QGraphicsTextItem
  -- TODO mkMethod "addWidget" [ptrT $ objT c_QWidget] $ ptrT $ objT c_QGraphicsProxyWidget
  -- TODO mkMethod' "addWidget" "addWidgetAll" [ptrT $ objT c_QWidget, enumT e_WindowFlags] $
  --   ptrT $ objT c_QGraphicsProxyWidget
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"backgroundBrush" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QBrush
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"bspTreeDepth" [Parameter]
np Type
intT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"clearFocus" [Parameter]
np Type
voidT
  -- TODO mkConstMethod "collidingItems" [ptrT $ objT c_QGraphicsItem] $
  --   objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod' "collidingItems" "collidingItemsAll"
  --   [ptrT $ objT c_QGraphicsItem, objT c_Qt::ItemSelectionMode] $
  --     objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkMethod "createItemGroup" [objT c_QList<QGraphicsItem] $ ptrT $ objT c_QGraphicsItemGroup
  -- TODO mkMethod "destroyItemGroup" [ptrT $ objT c_QGraphicsItemGroup] voidT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ 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
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> Type -> ClassEntity
mkProp String
"font" (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QFont
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"foregroundBrush" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QBrush
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"hasFocus" [Parameter]
np Type
boolT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"height" [Parameter]
np Type
qreal
  -- TODO mkConstMethod "inputMethodQuery" [objT c_Qt::InputMethodQuery] $ objT c_QVariant
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"invalidate" [Type
qreal, Type
qreal, Type
qreal, Type
qreal] Type
voidT
  -- TODO mkMethod' "invalidate" "invalidateAll"
  --   [qreal, qreal, qreal, qreal, objT c_SceneLayers] voidT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isActive" [Parameter]
np Type
boolT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"itemAt" String
"itemAtPointF" [Class -> Type
objT Class
c_QPointF, Class -> Type
objT Class
c_QTransform] (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
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"itemAt" String
"itemAtRaw" [Type
qreal, Type
qreal, Class -> Type
objT Class
c_QTransform] (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 "itemIndexMethod" np $ objT c_ItemIndexMethod
  -- TODO mkConstMethod' "items" "items" np $ objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod' "items" "itemsAll" [enumT e_SortOrder] $
  --   objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod' "items" "items" [objT c_QPointF] $
  --   objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod' "items" "itemsAll"
  --   [objT c_QPointF, objT c_Qt::ItemSelectionMode, objT c_Qt::SortOrder, objT c_QTransform] $
  --     objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod' "items" "items" [objT c_QRectF] $
  --   objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod' "items" "itemsAll"
  --   [objT c_QRectF, objT c_Qt::ItemSelectionMode, objT c_Qt::SortOrder, objT c_QTransform] $
  --     objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod' "items" "items" [objT c_QPolygonF] $
  --   objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod' "items" "itemsAll"
  --   [objT c_QPolygonF, objT c_Qt::ItemSelectionMode, objT c_Qt::SortOrder, objT c_QTransform] $
  --     objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod' "items" "items" [objT c_QPainterPath] $
  --   objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod' "items" "itemsAll"
  --   [objT c_QPainterPath, objT c_Qt::ItemSelectionMode
  --   , objT c_Qt::SortOrder, objT c_QTransform
  --   ] $ objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod' "items" "items"
  --   [qreal, qreal, qreal, qreal, objT c_Qt::ItemSelectionMode, objT c_Qt::SortOrder] $
  --     objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod' "items" "itemsAll"
  --   [ qreal, qreal, qreal, qreal, objT c_Qt::ItemSelectionMode
  --   , objT c_Qt::SortOrder, objT c_QTransform
  --   ] $ objT c_QList<QGraphicsItem $ objT c_*>
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"itemsBoundingRect" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QRectF
  , Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
4]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"minimumRenderSize" [Parameter]
np Type
qreal
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"mouseGrabberItem" [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 "palette" np $ objT c_QPalette
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"removeItem" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] Type
voidT
  -- TODO mkMethod "render" [ptrT $ objT c_QPainter] voidT
  -- TODO mkMethod' "render" "renderAll"
  --   [ptrT $ objT c_QPainter, objT c_QRectF, objT c_QRectF, enumT e_AspectRatioMode] voidT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"sceneRect" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QRectF
  -- TODO mkConstMethod "selectedItems" np $ objT c_QList<QGraphicsItem $ objT c_*>
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"selectionArea" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPainterPath
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"sendEvent" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem, Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QEvent] Type
boolT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setActivePanel" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] Type
voidT
  -- TODO mkMethod "setActiveWindow" [ptrT $ objT c_QGraphicsWidget] voidT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setBackgroundBrush" [Class -> Type
objT Class
c_QBrush] Type
voidT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setBspTreeDepth" [Type
intT] Type
voidT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setFocus" [Parameter]
np Type
voidT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"setFocus" String
"setFocusAll" [CppEnum -> Type
enumT CppEnum
e_FocusReason] Type
voidT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setFocusItem" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem] Type
voidT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"setFocusItem" String
"setFocusItemAll"
      [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem, CppEnum -> Type
enumT CppEnum
e_FocusReason] Type
voidT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setForegroundBrush" [Class -> Type
objT Class
c_QBrush] Type
voidT
  -- TODO mkMethod "setItemIndexMethod" [objT c_ItemIndexMethod] voidT
  , Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
4]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setMinimumRenderSize" [Type
qreal] Type
voidT
  -- TODO mkMethod "setPalette" [objT c_QPalette] voidT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setSceneRect" [Class -> Type
objT Class
c_QRectF] Type
voidT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"setSceneRect" String
"setSceneRectRaw" [Type
qreal, Type
qreal, Type
qreal, Type
qreal] Type
voidT
  , Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"setSelectionArea" String
"setSelectionAreaTransform"
      [Class -> Type
objT Class
c_QPainterPath, Class -> Type
objT Class
c_QTransform] Type
voidT
  , Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setSelectionArea" [Class -> Type
objT Class
c_QPainterPath] Type
voidT
  -- TODO mkMethod' "setSelectionArea" "setSelectionAreaAll"
  --   [objT c_QPainterPath, objT c_Qt::ItemSelectionMode, objT c_QTransform] voidT
  -- TODO mkMethod' "setSelectionArea" "setSelectionArea"
  --   [objT c_QPainterPath, objT c_Qt::ItemSelectionOperation] voidT
  -- TODO mkMethod' "setSelectionArea" "setSelectionAreaAll"
  --   [ objT c_QPainterPath, objT c_Qt::ItemSelectionOperation
  --   , objT c_Qt::ItemSelectionMode, objT c_QTransform
  --   ] voidT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setStickyFocus" [Type
boolT] Type
voidT
  -- TODO mkMethod "setStyle" [ptrT $ objT c_QStyle] voidT
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"stickyFocus" [Parameter]
np Type
boolT
  -- TODO mkConstMethod "style" np $ ptrT $ objT c_QStyle
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"update" [Type
qreal, Type
qreal, Type
qreal, Type
qreal] Type
voidT
  -- TODO mkConstMethod "views" np $ objT c_QList<QGraphicsView $ objT c_*>
  , ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"width" [Parameter]
np Type
qreal
  ]

e_ItemIndexMethod :: CppEnum
e_ItemIndexMethod =
  Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QGraphicsScene" String
"ItemIndexMethod")
  [String -> Include
includeStd String
"QGraphicsScene"]
  [ String
"BspTreeIndex"
  , String
"NoIndex"
  ]

(CppEnum
e_SceneLayer, Flags
fl_SceneLayers) =
  Identifier -> String -> [Include] -> [String] -> (CppEnum, Flags)
makeQtEnumAndFlags (String -> String -> Identifier
ident1 String
"QGraphicsScene" String
"SceneLayer") String
"SceneLayers"
  [String -> Include
includeStd String
"QGraphicsScene"]
  [ String
"ItemLayer"
  , String
"BackgroundLayer"
  , String
"ForegroundLayer"
  , String
"AllLayers"
  ]