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

module GI.Gtk.Objects.AspectFrame
    ( 

-- * Exported types
    AspectFrame(..)                         ,
    AspectFrameK                            ,
    toAspectFrame                           ,
    noAspectFrame                           ,


 -- * Methods
-- ** aspectFrameNew
    aspectFrameNew                          ,


-- ** aspectFrameSet
    aspectFrameSet                          ,




 -- * Properties
-- ** ObeyChild
    AspectFrameObeyChildPropertyInfo        ,
    constructAspectFrameObeyChild           ,
    getAspectFrameObeyChild                 ,
    setAspectFrameObeyChild                 ,


-- ** Ratio
    AspectFrameRatioPropertyInfo            ,
    constructAspectFrameRatio               ,
    getAspectFrameRatio                     ,
    setAspectFrameRatio                     ,


-- ** Xalign
    AspectFrameXalignPropertyInfo           ,
    constructAspectFrameXalign              ,
    getAspectFrameXalign                    ,
    setAspectFrameXalign                    ,


-- ** Yalign
    AspectFrameYalignPropertyInfo           ,
    constructAspectFrameYalign              ,
    getAspectFrameYalign                    ,
    setAspectFrameYalign                    ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gtk.Types
import GI.Gtk.Callbacks
import qualified GI.Atk as Atk
import qualified GI.GObject as GObject

newtype AspectFrame = AspectFrame (ForeignPtr AspectFrame)
foreign import ccall "gtk_aspect_frame_get_type"
    c_gtk_aspect_frame_get_type :: IO GType

type instance ParentTypes AspectFrame = AspectFrameParentTypes
type AspectFrameParentTypes = '[Frame, Bin, Container, Widget, GObject.Object, Atk.ImplementorIface, Buildable]

instance GObject AspectFrame where
    gobjectIsInitiallyUnowned _ = True
    gobjectType _ = c_gtk_aspect_frame_get_type
    

class GObject o => AspectFrameK o
instance (GObject o, IsDescendantOf AspectFrame o) => AspectFrameK o

toAspectFrame :: AspectFrameK o => o -> IO AspectFrame
toAspectFrame = unsafeCastTo AspectFrame

noAspectFrame :: Maybe AspectFrame
noAspectFrame = Nothing

-- VVV Prop "obey-child"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getAspectFrameObeyChild :: (MonadIO m, AspectFrameK o) => o -> m Bool
getAspectFrameObeyChild obj = liftIO $ getObjectPropertyBool obj "obey-child"

setAspectFrameObeyChild :: (MonadIO m, AspectFrameK o) => o -> Bool -> m ()
setAspectFrameObeyChild obj val = liftIO $ setObjectPropertyBool obj "obey-child" val

constructAspectFrameObeyChild :: Bool -> IO ([Char], GValue)
constructAspectFrameObeyChild val = constructObjectPropertyBool "obey-child" val

data AspectFrameObeyChildPropertyInfo
instance AttrInfo AspectFrameObeyChildPropertyInfo where
    type AttrAllowedOps AspectFrameObeyChildPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint AspectFrameObeyChildPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint AspectFrameObeyChildPropertyInfo = AspectFrameK
    type AttrGetType AspectFrameObeyChildPropertyInfo = Bool
    type AttrLabel AspectFrameObeyChildPropertyInfo = "AspectFrame::obey-child"
    attrGet _ = getAspectFrameObeyChild
    attrSet _ = setAspectFrameObeyChild
    attrConstruct _ = constructAspectFrameObeyChild

-- VVV Prop "ratio"
   -- Type: TBasicType TFloat
   -- Flags: [PropertyReadable,PropertyWritable]

getAspectFrameRatio :: (MonadIO m, AspectFrameK o) => o -> m Float
getAspectFrameRatio obj = liftIO $ getObjectPropertyFloat obj "ratio"

setAspectFrameRatio :: (MonadIO m, AspectFrameK o) => o -> Float -> m ()
setAspectFrameRatio obj val = liftIO $ setObjectPropertyFloat obj "ratio" val

constructAspectFrameRatio :: Float -> IO ([Char], GValue)
constructAspectFrameRatio val = constructObjectPropertyFloat "ratio" val

data AspectFrameRatioPropertyInfo
instance AttrInfo AspectFrameRatioPropertyInfo where
    type AttrAllowedOps AspectFrameRatioPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint AspectFrameRatioPropertyInfo = (~) Float
    type AttrBaseTypeConstraint AspectFrameRatioPropertyInfo = AspectFrameK
    type AttrGetType AspectFrameRatioPropertyInfo = Float
    type AttrLabel AspectFrameRatioPropertyInfo = "AspectFrame::ratio"
    attrGet _ = getAspectFrameRatio
    attrSet _ = setAspectFrameRatio
    attrConstruct _ = constructAspectFrameRatio

-- VVV Prop "xalign"
   -- Type: TBasicType TFloat
   -- Flags: [PropertyReadable,PropertyWritable]

getAspectFrameXalign :: (MonadIO m, AspectFrameK o) => o -> m Float
getAspectFrameXalign obj = liftIO $ getObjectPropertyFloat obj "xalign"

setAspectFrameXalign :: (MonadIO m, AspectFrameK o) => o -> Float -> m ()
setAspectFrameXalign obj val = liftIO $ setObjectPropertyFloat obj "xalign" val

constructAspectFrameXalign :: Float -> IO ([Char], GValue)
constructAspectFrameXalign val = constructObjectPropertyFloat "xalign" val

data AspectFrameXalignPropertyInfo
instance AttrInfo AspectFrameXalignPropertyInfo where
    type AttrAllowedOps AspectFrameXalignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint AspectFrameXalignPropertyInfo = (~) Float
    type AttrBaseTypeConstraint AspectFrameXalignPropertyInfo = AspectFrameK
    type AttrGetType AspectFrameXalignPropertyInfo = Float
    type AttrLabel AspectFrameXalignPropertyInfo = "AspectFrame::xalign"
    attrGet _ = getAspectFrameXalign
    attrSet _ = setAspectFrameXalign
    attrConstruct _ = constructAspectFrameXalign

-- VVV Prop "yalign"
   -- Type: TBasicType TFloat
   -- Flags: [PropertyReadable,PropertyWritable]

getAspectFrameYalign :: (MonadIO m, AspectFrameK o) => o -> m Float
getAspectFrameYalign obj = liftIO $ getObjectPropertyFloat obj "yalign"

setAspectFrameYalign :: (MonadIO m, AspectFrameK o) => o -> Float -> m ()
setAspectFrameYalign obj val = liftIO $ setObjectPropertyFloat obj "yalign" val

constructAspectFrameYalign :: Float -> IO ([Char], GValue)
constructAspectFrameYalign val = constructObjectPropertyFloat "yalign" val

data AspectFrameYalignPropertyInfo
instance AttrInfo AspectFrameYalignPropertyInfo where
    type AttrAllowedOps AspectFrameYalignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint AspectFrameYalignPropertyInfo = (~) Float
    type AttrBaseTypeConstraint AspectFrameYalignPropertyInfo = AspectFrameK
    type AttrGetType AspectFrameYalignPropertyInfo = Float
    type AttrLabel AspectFrameYalignPropertyInfo = "AspectFrame::yalign"
    attrGet _ = getAspectFrameYalign
    attrSet _ = setAspectFrameYalign
    attrConstruct _ = constructAspectFrameYalign

type instance AttributeList AspectFrame = AspectFrameAttributeList
type AspectFrameAttributeList = ('[ '("app-paintable", WidgetAppPaintablePropertyInfo), '("border-width", ContainerBorderWidthPropertyInfo), '("can-default", WidgetCanDefaultPropertyInfo), '("can-focus", WidgetCanFocusPropertyInfo), '("child", ContainerChildPropertyInfo), '("composite-child", WidgetCompositeChildPropertyInfo), '("double-buffered", WidgetDoubleBufferedPropertyInfo), '("events", WidgetEventsPropertyInfo), '("expand", WidgetExpandPropertyInfo), '("halign", WidgetHalignPropertyInfo), '("has-default", WidgetHasDefaultPropertyInfo), '("has-focus", WidgetHasFocusPropertyInfo), '("has-tooltip", WidgetHasTooltipPropertyInfo), '("height-request", WidgetHeightRequestPropertyInfo), '("hexpand", WidgetHexpandPropertyInfo), '("hexpand-set", WidgetHexpandSetPropertyInfo), '("is-focus", WidgetIsFocusPropertyInfo), '("label", FrameLabelPropertyInfo), '("label-widget", FrameLabelWidgetPropertyInfo), '("label-xalign", FrameLabelXalignPropertyInfo), '("label-yalign", FrameLabelYalignPropertyInfo), '("margin", WidgetMarginPropertyInfo), '("margin-bottom", WidgetMarginBottomPropertyInfo), '("margin-end", WidgetMarginEndPropertyInfo), '("margin-left", WidgetMarginLeftPropertyInfo), '("margin-right", WidgetMarginRightPropertyInfo), '("margin-start", WidgetMarginStartPropertyInfo), '("margin-top", WidgetMarginTopPropertyInfo), '("name", WidgetNamePropertyInfo), '("no-show-all", WidgetNoShowAllPropertyInfo), '("obey-child", AspectFrameObeyChildPropertyInfo), '("opacity", WidgetOpacityPropertyInfo), '("parent", WidgetParentPropertyInfo), '("ratio", AspectFrameRatioPropertyInfo), '("receives-default", WidgetReceivesDefaultPropertyInfo), '("resize-mode", ContainerResizeModePropertyInfo), '("scale-factor", WidgetScaleFactorPropertyInfo), '("sensitive", WidgetSensitivePropertyInfo), '("shadow-type", FrameShadowTypePropertyInfo), '("style", WidgetStylePropertyInfo), '("tooltip-markup", WidgetTooltipMarkupPropertyInfo), '("tooltip-text", WidgetTooltipTextPropertyInfo), '("valign", WidgetValignPropertyInfo), '("vexpand", WidgetVexpandPropertyInfo), '("vexpand-set", WidgetVexpandSetPropertyInfo), '("visible", WidgetVisiblePropertyInfo), '("width-request", WidgetWidthRequestPropertyInfo), '("window", WidgetWindowPropertyInfo), '("xalign", AspectFrameXalignPropertyInfo), '("yalign", AspectFrameYalignPropertyInfo)] :: [(Symbol, *)])

type instance SignalList AspectFrame = AspectFrameSignalList
type AspectFrameSignalList = ('[ '("accel-closures-changed", WidgetAccelClosuresChangedSignalInfo), '("add", ContainerAddSignalInfo), '("button-press-event", WidgetButtonPressEventSignalInfo), '("button-release-event", WidgetButtonReleaseEventSignalInfo), '("can-activate-accel", WidgetCanActivateAccelSignalInfo), '("check-resize", ContainerCheckResizeSignalInfo), '("child-notify", WidgetChildNotifySignalInfo), '("composited-changed", WidgetCompositedChangedSignalInfo), '("configure-event", WidgetConfigureEventSignalInfo), '("damage-event", WidgetDamageEventSignalInfo), '("delete-event", WidgetDeleteEventSignalInfo), '("destroy", WidgetDestroySignalInfo), '("destroy-event", WidgetDestroyEventSignalInfo), '("direction-changed", WidgetDirectionChangedSignalInfo), '("drag-begin", WidgetDragBeginSignalInfo), '("drag-data-delete", WidgetDragDataDeleteSignalInfo), '("drag-data-get", WidgetDragDataGetSignalInfo), '("drag-data-received", WidgetDragDataReceivedSignalInfo), '("drag-drop", WidgetDragDropSignalInfo), '("drag-end", WidgetDragEndSignalInfo), '("drag-failed", WidgetDragFailedSignalInfo), '("drag-leave", WidgetDragLeaveSignalInfo), '("drag-motion", WidgetDragMotionSignalInfo), '("draw", WidgetDrawSignalInfo), '("enter-notify-event", WidgetEnterNotifyEventSignalInfo), '("event", WidgetEventSignalInfo), '("event-after", WidgetEventAfterSignalInfo), '("focus", WidgetFocusSignalInfo), '("focus-in-event", WidgetFocusInEventSignalInfo), '("focus-out-event", WidgetFocusOutEventSignalInfo), '("grab-broken-event", WidgetGrabBrokenEventSignalInfo), '("grab-focus", WidgetGrabFocusSignalInfo), '("grab-notify", WidgetGrabNotifySignalInfo), '("hide", WidgetHideSignalInfo), '("hierarchy-changed", WidgetHierarchyChangedSignalInfo), '("key-press-event", WidgetKeyPressEventSignalInfo), '("key-release-event", WidgetKeyReleaseEventSignalInfo), '("keynav-failed", WidgetKeynavFailedSignalInfo), '("leave-notify-event", WidgetLeaveNotifyEventSignalInfo), '("map", WidgetMapSignalInfo), '("map-event", WidgetMapEventSignalInfo), '("mnemonic-activate", WidgetMnemonicActivateSignalInfo), '("motion-notify-event", WidgetMotionNotifyEventSignalInfo), '("move-focus", WidgetMoveFocusSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("parent-set", WidgetParentSetSignalInfo), '("popup-menu", WidgetPopupMenuSignalInfo), '("property-notify-event", WidgetPropertyNotifyEventSignalInfo), '("proximity-in-event", WidgetProximityInEventSignalInfo), '("proximity-out-event", WidgetProximityOutEventSignalInfo), '("query-tooltip", WidgetQueryTooltipSignalInfo), '("realize", WidgetRealizeSignalInfo), '("remove", ContainerRemoveSignalInfo), '("screen-changed", WidgetScreenChangedSignalInfo), '("scroll-event", WidgetScrollEventSignalInfo), '("selection-clear-event", WidgetSelectionClearEventSignalInfo), '("selection-get", WidgetSelectionGetSignalInfo), '("selection-notify-event", WidgetSelectionNotifyEventSignalInfo), '("selection-received", WidgetSelectionReceivedSignalInfo), '("selection-request-event", WidgetSelectionRequestEventSignalInfo), '("set-focus-child", ContainerSetFocusChildSignalInfo), '("show", WidgetShowSignalInfo), '("show-help", WidgetShowHelpSignalInfo), '("size-allocate", WidgetSizeAllocateSignalInfo), '("state-changed", WidgetStateChangedSignalInfo), '("state-flags-changed", WidgetStateFlagsChangedSignalInfo), '("style-set", WidgetStyleSetSignalInfo), '("style-updated", WidgetStyleUpdatedSignalInfo), '("touch-event", WidgetTouchEventSignalInfo), '("unmap", WidgetUnmapSignalInfo), '("unmap-event", WidgetUnmapEventSignalInfo), '("unrealize", WidgetUnrealizeSignalInfo), '("visibility-notify-event", WidgetVisibilityNotifyEventSignalInfo), '("window-state-event", WidgetWindowStateEventSignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method AspectFrame::new
-- method type : Constructor
-- Args : [Arg {argName = "label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "xalign", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "yalign", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ratio", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "obey_child", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "xalign", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "yalign", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ratio", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "obey_child", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "AspectFrame"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_aspect_frame_new" gtk_aspect_frame_new :: 
    CString ->                              -- label : TBasicType TUTF8
    CFloat ->                               -- xalign : TBasicType TFloat
    CFloat ->                               -- yalign : TBasicType TFloat
    CFloat ->                               -- ratio : TBasicType TFloat
    CInt ->                                 -- obey_child : TBasicType TBoolean
    IO (Ptr AspectFrame)


aspectFrameNew ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- label
    Float ->                                -- xalign
    Float ->                                -- yalign
    Float ->                                -- ratio
    Bool ->                                 -- obey_child
    m AspectFrame
aspectFrameNew label xalign yalign ratio obey_child = liftIO $ do
    maybeLabel <- case label of
        Nothing -> return nullPtr
        Just jLabel -> do
            jLabel' <- textToCString jLabel
            return jLabel'
    let xalign' = realToFrac xalign
    let yalign' = realToFrac yalign
    let ratio' = realToFrac ratio
    let obey_child' = (fromIntegral . fromEnum) obey_child
    result <- gtk_aspect_frame_new maybeLabel xalign' yalign' ratio' obey_child'
    checkUnexpectedReturnNULL "gtk_aspect_frame_new" result
    result' <- (newObject AspectFrame) result
    freeMem maybeLabel
    return result'

-- method AspectFrame::set
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "AspectFrame", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "xalign", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "yalign", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ratio", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "obey_child", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "AspectFrame", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "xalign", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "yalign", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ratio", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "obey_child", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_aspect_frame_set" gtk_aspect_frame_set :: 
    Ptr AspectFrame ->                      -- _obj : TInterface "Gtk" "AspectFrame"
    CFloat ->                               -- xalign : TBasicType TFloat
    CFloat ->                               -- yalign : TBasicType TFloat
    CFloat ->                               -- ratio : TBasicType TFloat
    CInt ->                                 -- obey_child : TBasicType TBoolean
    IO ()


aspectFrameSet ::
    (MonadIO m, AspectFrameK a) =>
    a ->                                    -- _obj
    Float ->                                -- xalign
    Float ->                                -- yalign
    Float ->                                -- ratio
    Bool ->                                 -- obey_child
    m ()
aspectFrameSet _obj xalign yalign ratio obey_child = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let xalign' = realToFrac xalign
    let yalign' = realToFrac yalign
    let ratio' = realToFrac ratio
    let obey_child' = (fromIntegral . fromEnum) obey_child
    gtk_aspect_frame_set _obj' xalign' yalign' ratio' obey_child'
    touchManagedPtr _obj
    return ()