{- |
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.Interfaces.Orientable
    ( 

-- * Exported types
    Orientable(..)                          ,
    noOrientable                            ,
    OrientableK                             ,
    toOrientable                            ,


 -- * Methods
-- ** orientableGetOrientation
    orientableGetOrientation                ,


-- ** orientableSetOrientation
    orientableSetOrientation                ,




 -- * Properties
-- ** Orientation
    OrientableOrientationPropertyInfo       ,
    constructOrientableOrientation          ,
    getOrientableOrientation                ,
    setOrientableOrientation                ,




    ) 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.GObject as GObject

-- interface Orientable 

newtype Orientable = Orientable (ForeignPtr Orientable)
noOrientable :: Maybe Orientable
noOrientable = Nothing

-- VVV Prop "orientation"
   -- Type: TInterface "Gtk" "Orientation"
   -- Flags: [PropertyReadable,PropertyWritable]

getOrientableOrientation :: (MonadIO m, OrientableK o) => o -> m Orientation
getOrientableOrientation obj = liftIO $ getObjectPropertyEnum obj "orientation"

setOrientableOrientation :: (MonadIO m, OrientableK o) => o -> Orientation -> m ()
setOrientableOrientation obj val = liftIO $ setObjectPropertyEnum obj "orientation" val

constructOrientableOrientation :: Orientation -> IO ([Char], GValue)
constructOrientableOrientation val = constructObjectPropertyEnum "orientation" val

data OrientableOrientationPropertyInfo
instance AttrInfo OrientableOrientationPropertyInfo where
    type AttrAllowedOps OrientableOrientationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint OrientableOrientationPropertyInfo = (~) Orientation
    type AttrBaseTypeConstraint OrientableOrientationPropertyInfo = OrientableK
    type AttrGetType OrientableOrientationPropertyInfo = Orientation
    type AttrLabel OrientableOrientationPropertyInfo = "Orientable::orientation"
    attrGet _ = getOrientableOrientation
    attrSet _ = setOrientableOrientation
    attrConstruct _ = constructOrientableOrientation

type instance AttributeList Orientable = OrientableAttributeList
type OrientableAttributeList = ('[ '("orientation", OrientableOrientationPropertyInfo)] :: [(Symbol, *)])

type instance SignalList Orientable = OrientableSignalList
type OrientableSignalList = ('[ '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

foreign import ccall "gtk_orientable_get_type"
    c_gtk_orientable_get_type :: IO GType

type instance ParentTypes Orientable = OrientableParentTypes
type OrientableParentTypes = '[GObject.Object]

instance GObject Orientable where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_gtk_orientable_get_type
    

class GObject o => OrientableK o
instance (GObject o, IsDescendantOf Orientable o) => OrientableK o

toOrientable :: OrientableK o => o -> IO Orientable
toOrientable = unsafeCastTo Orientable

-- method Orientable::get_orientation
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Orientable", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Orientable", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "Orientation"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_orientable_get_orientation" gtk_orientable_get_orientation :: 
    Ptr Orientable ->                       -- _obj : TInterface "Gtk" "Orientable"
    IO CUInt


orientableGetOrientation ::
    (MonadIO m, OrientableK a) =>
    a ->                                    -- _obj
    m Orientation
orientableGetOrientation _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_orientable_get_orientation _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method Orientable::set_orientation
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Orientable", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "orientation", argType = TInterface "Gtk" "Orientation", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Orientable", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "orientation", argType = TInterface "Gtk" "Orientation", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_orientable_set_orientation" gtk_orientable_set_orientation :: 
    Ptr Orientable ->                       -- _obj : TInterface "Gtk" "Orientable"
    CUInt ->                                -- orientation : TInterface "Gtk" "Orientation"
    IO ()


orientableSetOrientation ::
    (MonadIO m, OrientableK a) =>
    a ->                                    -- _obj
    Orientation ->                          -- orientation
    m ()
orientableSetOrientation _obj orientation = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let orientation' = (fromIntegral . fromEnum) orientation
    gtk_orientable_set_orientation _obj' orientation'
    touchManagedPtr _obj
    return ()