-- 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.QGraphicsView (
  aModule,
  c_QGraphicsView,
  e_DragMode,
  e_ViewportAnchor,
  e_ViewportUpdateMode,
  e_OptimizationFlag,
  fl_OptimizationFlags,
  e_CacheModeFlag,
  fl_CacheMode
  ) where

import Foreign.Hoppy.Generator.Spec (
  addReqIncludes,
  classSetEntityPrefix,
  ident,
  ident1,
  includeStd,
  makeClass,
  mkMethod,
  mkMethod',
  mkConstMethod,
  mkConstMethod',
  mkCtor,
  np,
  )
import Foreign.Hoppy.Generator.Types (
  boolT,
  constT,
  enumT,
  intT,
  objT,
  ptrT,
  voidT,
  )
import Graphics.UI.Qtah.Generator.Flags (flagsT)
import Graphics.UI.Qtah.Generator.Interface.Core.Types (e_AspectRatioMode, fl_Alignment, qreal)
import Graphics.UI.Qtah.Generator.Interface.Core.QPoint (c_QPoint)
import Graphics.UI.Qtah.Generator.Interface.Core.QPointF (c_QPointF)
import Graphics.UI.Qtah.Generator.Interface.Core.QRect (c_QRect)
import Graphics.UI.Qtah.Generator.Interface.Core.QRectF (c_QRectF)
import Graphics.UI.Qtah.Generator.Interface.Gui.QBrush (c_QBrush)
import Graphics.UI.Qtah.Generator.Interface.Gui.QPainter (c_QPainter, e_RenderHint, fl_RenderHints)
import Graphics.UI.Qtah.Generator.Interface.Gui.QPolygon (c_QPolygon)
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.Gui.QPainter
import Graphics.UI.Qtah.Generator.Interface.Gui.QPainterPath (c_QPainterPath)
import Graphics.UI.Qtah.Generator.Interface.Widgets.QAbstractScrollArea (c_QAbstractScrollArea)
import Graphics.UI.Qtah.Generator.Interface.Widgets.QGraphicsItem (c_QGraphicsItem)
import Graphics.UI.Qtah.Generator.Interface.Widgets.QGraphicsScene (c_QGraphicsScene)
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
"QGraphicsView"] ([QtExport] -> QtModule) -> [QtExport] -> QtModule
forall a b. (a -> b) -> a -> b
$
  [ Class -> QtExport
forall a. Exportable a => a -> QtExport
qtExport Class
c_QGraphicsView
  , CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_CacheModeFlag
  , Flags -> QtExport
forall a. Exportable a => a -> QtExport
qtExport Flags
fl_CacheMode
  , CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_DragMode
  , CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_OptimizationFlag
  , Flags -> QtExport
forall a. Exportable a => a -> QtExport
qtExport Flags
fl_OptimizationFlags
  , CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_ViewportAnchor
  , CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_ViewportUpdateMode
  ]

c_QGraphicsView :: Class
c_QGraphicsView =
  [Include] -> Class -> Class
forall a. HasReqs a => [Include] -> a -> a
addReqIncludes [String -> Include
includeStd String
"QGraphicsView"] (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
"QGraphicsView") Maybe ExtName
forall a. Maybe a
Nothing [Class
c_QAbstractScrollArea]
  [ String -> [Parameter] -> ClassEntity
forall p. IsParameter p => String -> [p] -> ClassEntity
mkCtor String
"new" [Parameter]
np
  , String -> [Type] -> ClassEntity
forall p. IsParameter p => String -> [p] -> ClassEntity
mkCtor String
"newWithScene" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsScene]
  , 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_QWidget]
  , String -> [Type] -> ClassEntity
forall p. IsParameter p => String -> [p] -> ClassEntity
mkCtor String
"newWithSceneAndParent" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsScene, Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QWidget]
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"alignment" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Flags -> Type
flagsT Flags
fl_Alignment
  , 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
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"cacheMode" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Flags -> Type
flagsT Flags
fl_CacheMode
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"centerOn" String
"centerOnPointF" [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
"centerOn" String
"centerOnRaw" [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
"centerOn" String
"centerOnItem" [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
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"dragMode" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_DragMode
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"ensureVisible" String
"ensureVisibleRectF" [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
"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
"ensureVisibleItem"
      [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
  , 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
"ensureVisibleRawAll"
      [Type
qreal, Type
qreal, Type
qreal, Type
qreal, 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
"ensureVisibleItemAll"
      [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
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
"fitInView" String
"fitInViewRectF" [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
"fitInView" String
"fitInViewRect" [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
"fitInView" String
"fitInViewItem" [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
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"fitInView" String
"fitInViewRectFAll" [Class -> Type
objT Class
c_QRectF, CppEnum -> Type
enumT CppEnum
e_AspectRatioMode] Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"fitInView" String
"fitInViewRectAll"
      [Type
qreal, Type
qreal, Type
qreal, Type
qreal, CppEnum -> Type
enumT CppEnum
e_AspectRatioMode] Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"fitInView" String
"fitInViewItemAll"
      [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, CppEnum -> Type
enumT CppEnum
e_AspectRatioMode] Type
voidT
  , 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
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isInteractive" [Parameter]
np Type
boolT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isTransformed" [Parameter]
np Type
boolT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"itemAt" String
"itemAtPoint" [Class -> Type
objT Class
c_QPoint] (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 -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"itemAt" String
"itemAtRaw" [Type
intT, Type
intT] (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 "items" np $ objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod "items" [objT c_QPoint] $ objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod "items" [intT, intT] $ objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod "items" [intT, intT, intT, intT, objT c_Qt::ItemSelectionMode] $
  --   objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod "items" [objT c_QRect, objT c_Qt::ItemSelectionMode] $
  --   objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod "items" [objT c_QPolygon, objT c_Qt::ItemSelectionMode] $
  --   objT c_QList<QGraphicsItem $ objT c_*>
  -- TODO mkConstMethod "items" [objT c_QPainterPath, objT c_Qt::ItemSelectionMode] $
  --   objT c_QList<QGraphicsItem $ objT c_*>
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"mapFromScene" String
"mapFromScenePointF"
      [Class -> Type
objT Class
c_QPointF] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPoint
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"mapFromScene" String
"mapFromSceneRectF"
      [Class -> Type
objT Class
c_QRectF] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPolygon
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"mapFromScene" String
"mapFromScenePolygonF"
      [Class -> Type
objT Class
c_QPolygonF] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPolygon
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"mapFromScene" String
"mapFromScenePainterPath"
      [Class -> Type
objT Class
c_QPainterPath] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPainterPath
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"mapFromScene" String
"mapFromScenePointFRaw"
      [Type
qreal, Type
qreal] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPoint
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"mapFromScene" String
"mapFromSceneRectFRaw"
      [Type
qreal, Type
qreal, Type
qreal, Type
qreal] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPolygon
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"mapToScene" String
"mapToScenePoint"
      [Class -> Type
objT Class
c_QPoint] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPointF
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"mapToScene" String
"mapToSceneRect"
      [Class -> Type
objT Class
c_QRect] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPolygonF
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"mapToScene" String
"mapToScenePolygon"
      [Class -> Type
objT Class
c_QPolygon] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPolygonF
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"mapToScene" String
"mapToScenePainterPath"
      [Class -> Type
objT Class
c_QPainterPath] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPainterPath
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"mapToScene" String
"mapToScenePointRaw"
      [Type
intT, Type
intT] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPointF
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"mapToScene" String
"mapToSceneRectRaw"
      [Type
intT, Type
intT, Type
intT, Type
intT] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPolygonF
  -- TODO mkConstMethod "matrix" np $ objT c_QMatrix
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"optimizationFlags" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Flags -> Type
flagsT Flags
fl_OptimizationFlags
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"render" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPainter] Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"render" String
"renderAll"
      [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPainter, Class -> Type
objT Class
c_QRectF, Class -> Type
objT Class
c_QRect, CppEnum -> Type
enumT CppEnum
e_AspectRatioMode] Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"renderHints" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Flags -> Type
flagsT Flags
fl_RenderHints
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"resetCachedContent" [Parameter]
np Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"resetMatrix" [Parameter]
np 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
"resizeAnchor" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_ViewportAnchor
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"rotate" [Type
qreal] Type
voidT
  -- TODO mkConstMethod "rubberBandSelectionMode" np $ objT c_Qt::ItemSelectionMode
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"scale" [Type
qreal, Type
qreal] Type
voidT
  , 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
"sceneRect" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QRectF
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setAlignment" [Flags -> Type
flagsT Flags
fl_Alignment] Type
voidT
  , 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
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setCacheMode" [Flags -> Type
flagsT Flags
fl_CacheMode] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setDragMode" [CppEnum -> Type
enumT CppEnum
e_DragMode] Type
voidT
  , 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
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setInteractive" [Type
boolT] Type
voidT
  -- TODO mkMethod "setMatrix" [objT c_QMatrix] voidT
  -- TODO mkMethod' "setMatrix" "setMatrixAll" [objT c_QMatrix, boolT] voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setOptimizationFlag" [CppEnum -> Type
enumT CppEnum
e_OptimizationFlag] Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"setOptimizationFlag" String
"setOptimizationFlagAll" [CppEnum -> Type
enumT CppEnum
e_OptimizationFlag, Type
boolT] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setOptimizationFlags" [Flags -> Type
flagsT Flags
fl_OptimizationFlags] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setRenderHint" [CppEnum -> Type
enumT CppEnum
e_RenderHint] Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"setRenderHint" String
"setRenderHintAll" [CppEnum -> Type
enumT CppEnum
e_RenderHint, Type
boolT] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setRenderHints" [Flags -> Type
flagsT Flags
fl_RenderHints] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setResizeAnchor" [CppEnum -> Type
enumT CppEnum
e_ViewportAnchor] Type
voidT
  -- TODO mkMethod "setRubberBandSelectionMode" [objT c_Qt::ItemSelectionMode] voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setScene" [Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsScene] Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"setSceneRect" String
"setSceneRectF" [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
"setSceneRect" String
"setSceneRectRaw" [Type
qreal, Type
qreal, Type
qreal, Type
qreal] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setTransform" [Class -> Type
objT Class
c_QTransform] Type
voidT
  , String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"setTransform" String
"setTransformAll" [Class -> Type
objT Class
c_QTransform, Type
boolT] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setTransformationAnchor" [CppEnum -> Type
enumT CppEnum
e_ViewportAnchor] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"setViewportUpdateMode" [CppEnum -> Type
enumT CppEnum
e_ViewportUpdateMode] Type
voidT
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"shear" [Type
qreal, Type
qreal] Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"transform" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QTransform
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"transformationAnchor" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_ViewportAnchor
  , String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkMethod String
"translate" [Type
qreal, Type
qreal] Type
voidT
  , String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"viewportTransform" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QTransform
  ]

(CppEnum
e_CacheModeFlag, Flags
fl_CacheMode) =
  Identifier -> String -> [Include] -> [String] -> (CppEnum, Flags)
makeQtEnumAndFlags (String -> String -> Identifier
ident1 String
"QGraphicsView" String
"CacheModeFlag") String
"CacheMode"
  [String -> Include
includeStd String
"QGraphicsView"]
  [ String
"CacheNone"
  , String
"CacheBackground"
  ]

e_DragMode :: CppEnum
e_DragMode =
  Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QGraphicsView" String
"DragMode") [String -> Include
includeStd String
"QGraphicsView"]
  [ String
"NoDrag"
  , String
"ScrollHandDrag"
  , String
"RubberBandDrag"
  ]

(CppEnum
e_OptimizationFlag, Flags
fl_OptimizationFlags) =
  Identifier -> String -> [Include] -> [String] -> (CppEnum, Flags)
makeQtEnumAndFlags (String -> String -> Identifier
ident1 String
"QGraphicsView" String
"OptimizationFlag") String
"OptimizationFlags"
  [String -> Include
includeStd String
"QGraphicsView"]
  [ String
"DontClipPainter"
  , String
"DontSavePainterState"
  , String
"DontAdjustForAntialiasing"
  , String
"IndirectPainting"
  ]

e_ViewportAnchor :: CppEnum
e_ViewportAnchor =
  Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QGraphicsView" String
"ViewportAnchor")
  [String -> Include
includeStd String
"QGraphicsView"]
  [ String
"NoAnchor"
  , String
"AnchorViewCenter"
  , String
"AnchorUnderMouse"
  ]

e_ViewportUpdateMode :: CppEnum
e_ViewportUpdateMode =
  Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QGraphicsView" String
"ViewportUpdateMode")
  [String -> Include
includeStd String
"QGraphicsView"]
  [ String
"FullViewportUpdate"
  , String
"MinimalViewportUpdate"
  , String
"SmartViewportUpdate"
  , String
"BoundingRectViewportUpdate"
  , String
"NoViewportUpdate"
  ]

-- Methods with optional arguments that weren't handled properly in the bindings above
-- (i.e. `foo` + `fooAll`).
{-
QList<QGraphicsItem *>  items
  (int x, int y, int w, int h, Qt::ItemSelectionMode mode = Qt::IntersectsItemShape) const
QList<QGraphicsItem *>  items
  (const QRect & rect, Qt::ItemSelectionMode mode = Qt::IntersectsItemShape) const
QList<QGraphicsItem *>  items
  (const QPolygon & polygon, Qt::ItemSelectionMode mode = Qt::IntersectsItemShape) const
QList<QGraphicsItem *>  items
  (const QPainterPath & path, Qt::ItemSelectionMode mode = Qt::IntersectsItemShape) const
-}