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

#GtkRadioActionEntry structs are used with
gtk_action_group_add_radio_actions() to construct groups of radio actions.
-}

module GI.Gtk.Structs.RadioActionEntry
    ( 

-- * Exported types
    RadioActionEntry(..)                    ,
    noRadioActionEntry                      ,


 -- * Properties
-- ** Accelerator
    radioActionEntryReadAccelerator         ,


-- ** Label
    radioActionEntryReadLabel               ,


-- ** Name
    radioActionEntryReadName                ,


-- ** StockId
    radioActionEntryReadStockId             ,


-- ** Tooltip
    radioActionEntryReadTooltip             ,


-- ** Value
    radioActionEntryReadValue               ,




    ) 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

newtype RadioActionEntry = RadioActionEntry (ForeignPtr RadioActionEntry)
noRadioActionEntry :: Maybe RadioActionEntry
noRadioActionEntry = Nothing

radioActionEntryReadName :: RadioActionEntry -> IO T.Text
radioActionEntryReadName s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CString
    val' <- cstringToText val
    return val'

radioActionEntryReadStockId :: RadioActionEntry -> IO T.Text
radioActionEntryReadStockId s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CString
    val' <- cstringToText val
    return val'

radioActionEntryReadLabel :: RadioActionEntry -> IO T.Text
radioActionEntryReadLabel s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO CString
    val' <- cstringToText val
    return val'

radioActionEntryReadAccelerator :: RadioActionEntry -> IO T.Text
radioActionEntryReadAccelerator s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO CString
    val' <- cstringToText val
    return val'

radioActionEntryReadTooltip :: RadioActionEntry -> IO T.Text
radioActionEntryReadTooltip s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO CString
    val' <- cstringToText val
    return val'

radioActionEntryReadValue :: RadioActionEntry -> IO Int32
radioActionEntryReadValue s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO Int32
    return val