module Graphics.UI.Gtk.ModelView.Types (
TypedTreeModel(..),
TypedTreeModelClass,
toTypedTreeModel,
unsafeTreeModelToGeneric,
TypedTreeModelSort(..),
unsafeTreeModelSortToGeneric,
TypedTreeModelFilter(..),
unsafeTreeModelFilterToGeneric,
TreeIter(..),
receiveTreeIter,
peekTreeIter,
treeIterSetStamp,
TreePath,
NativeTreePath(..),
newTreePath,
withTreePath,
maybeWithTreePath,
peekTreePath,
fromTreePath,
stringToTreePath,
ColumnAccess(..),
ColumnId(..),
comboQuark,
) where
import GHC.Exts (unsafeCoerce#)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.GValue (GValue)
import System.Glib.GObject (Quark, quarkFromString)
import Graphics.UI.Gtk.Types (TreeModel, TreeModelSort, TreeModelFilter,
Pixbuf)
import Data.Char ( isDigit )
import Control.Monad ( liftM )
newtype TypedTreeModel row = TypedTreeModel (ForeignPtr (TypedTreeModel row))
class TypedTreeModelClass model where
dummy :: model a -> a
dummy _ = error "not used"
toTypedTreeModel :: TypedTreeModelClass model => model row -> TypedTreeModel row
toTypedTreeModel = unsafeCoerce#
unsafeTreeModelToGeneric :: TreeModel -> model row
unsafeTreeModelToGeneric = unsafeCoerce#
instance TypedTreeModelClass TypedTreeModel
newtype TypedTreeModelSort row = TypedTreeModelSort (ForeignPtr (TypedTreeModelSort row))
unsafeTreeModelSortToGeneric :: TreeModelSort -> TypedTreeModelSort row
unsafeTreeModelSortToGeneric = unsafeCoerce#
instance TypedTreeModelClass TypedTreeModelSort
newtype TypedTreeModelFilter row = TypedTreeModelFilter (ForeignPtr (TypedTreeModelFilter row))
unsafeTreeModelFilterToGeneric :: TreeModelFilter -> TypedTreeModelFilter row
unsafeTreeModelFilterToGeneric = unsafeCoerce#
instance TypedTreeModelClass TypedTreeModelFilter
data TreeIter = TreeIter !CInt !Word32 !Word32 !Word32
deriving Show
type TreeIterPtr = Ptr (TreeIter)
instance Storable TreeIter where
sizeOf _ = 32
alignment _ = alignment (undefined :: CInt)
peek ptr = do
stamp <- (\ptr -> do {peekByteOff ptr 0 ::IO CInt}) ptr
user_data <- (\ptr -> do {peekByteOff ptr 8 ::IO (Ptr ())}) ptr
user_data2 <- (\ptr -> do {peekByteOff ptr 16 ::IO (Ptr ())}) ptr
user_data3 <- (\ptr -> do {peekByteOff ptr 24 ::IO (Ptr ())}) ptr
return (TreeIter stamp (ptrToWord user_data)
(ptrToWord user_data2)
(ptrToWord user_data3))
where ptrToWord :: Ptr a -> Word32
ptrToWord ptr = fromIntegral (ptr `minusPtr` nullPtr)
poke ptr (TreeIter stamp user_data user_data2 user_data3) = do
(\ptr val -> do {pokeByteOff ptr 0 (val::CInt)}) ptr stamp
(\ptr val -> do {pokeByteOff ptr 8 (val::(Ptr ()))}) ptr (wordToPtr user_data)
(\ptr val -> do {pokeByteOff ptr 16 (val::(Ptr ()))}) ptr (wordToPtr user_data2)
(\ptr val -> do {pokeByteOff ptr 24 (val::(Ptr ()))}) ptr (wordToPtr user_data3)
where wordToPtr :: Word32 -> Ptr a
wordToPtr word = nullPtr `plusPtr` fromIntegral word
receiveTreeIter :: (Ptr TreeIter -> IO CInt) -> IO (Maybe TreeIter)
receiveTreeIter body =
alloca $ \iterPtr -> do
result <- body iterPtr
if toBool result
then liftM Just (peek iterPtr)
else return Nothing
peekTreeIter :: Ptr TreeIter -> IO TreeIter
peekTreeIter ptr
| ptr==nullPtr = fail "peekTreeIter: ptr is NULL, tree iterator is invalid"
| otherwise = peek ptr
treeIterSetStamp :: TreeIter -> CInt -> TreeIter
treeIterSetStamp (TreeIter _ a b c) s = (TreeIter s a b c)
type TreePath = [Int]
newtype NativeTreePath = NativeTreePath (Ptr (NativeTreePath))
nativeTreePathFree :: NativeTreePath -> IO ()
nativeTreePathFree =
(\(NativeTreePath arg1) -> gtk_tree_path_free arg1)
newTreePath :: TreePath -> IO NativeTreePath
newTreePath path = do
nativePath <- liftM NativeTreePath gtk_tree_path_new
mapM_ ((\(NativeTreePath arg1) arg2 -> gtk_tree_path_append_index arg1 arg2) nativePath . fromIntegral) path
return nativePath
withTreePath :: TreePath -> (NativeTreePath -> IO a) -> IO a
withTreePath tp act = do
nativePath <- newTreePath tp
res <- act nativePath
nativeTreePathFree nativePath
return res
maybeWithTreePath :: Maybe TreePath -> (NativeTreePath -> IO a) -> IO a
maybeWithTreePath mbTp act = maybe (act (NativeTreePath nullPtr)) (`withTreePath` act) mbTp
nativeTreePathGetIndices :: NativeTreePath -> IO [Int]
nativeTreePathGetIndices tp = do
depth <- liftM fromIntegral $ (\(NativeTreePath arg1) -> gtk_tree_path_get_depth arg1) tp
arrayPtr <- (\(NativeTreePath arg1) -> gtk_tree_path_get_indices arg1) tp
if (depth==0 || arrayPtr==nullPtr)
then return []
else liftM (map fromIntegral) $ peekArray depth arrayPtr
peekTreePath :: Ptr NativeTreePath -> IO TreePath
peekTreePath tpPtr | tpPtr==nullPtr = return []
| otherwise =
nativeTreePathGetIndices (NativeTreePath tpPtr)
fromTreePath :: Ptr NativeTreePath -> IO TreePath
fromTreePath tpPtr | tpPtr==nullPtr = return []
| otherwise = do
path <- nativeTreePathGetIndices (NativeTreePath tpPtr)
nativeTreePathFree (NativeTreePath tpPtr)
return path
stringToTreePath :: DefaultGlibString -> TreePath
stringToTreePath = stringToTreePath' . glibToString
where
stringToTreePath' "" = []
stringToTreePath' path = getNum 0 (dropWhile (not . isDigit) path)
getNum acc ('0':xs) = getNum (10*acc) xs
getNum acc ('1':xs) = getNum (10*acc+1) xs
getNum acc ('2':xs) = getNum (10*acc+2) xs
getNum acc ('3':xs) = getNum (10*acc+3) xs
getNum acc ('4':xs) = getNum (10*acc+4) xs
getNum acc ('5':xs) = getNum (10*acc+5) xs
getNum acc ('6':xs) = getNum (10*acc+6) xs
getNum acc ('7':xs) = getNum (10*acc+7) xs
getNum acc ('8':xs) = getNum (10*acc+8) xs
getNum acc ('9':xs) = getNum (10*acc+9) xs
getNum acc xs = acc:stringToTreePath' (dropWhile (not . isDigit) xs)
data ColumnAccess row where
CAInvalid :: ColumnAccess row
CAInt :: (row -> Int) -> ColumnAccess row
CABool :: (row -> Bool) -> ColumnAccess row
CAString :: GlibString string => (row -> string) -> ColumnAccess row
CAPixbuf :: (row -> Pixbuf) -> ColumnAccess row
data ColumnId row ty
= ColumnId (GValue -> IO ty) ((row -> ty) -> ColumnAccess row) Int
comboQuark :: Quark
comboQuark =
unsafePerformIO $ quarkFromString ("comboBoxHaskellStringModelQuark"::DefaultGlibString)
foreign import ccall unsafe "gtk_tree_path_free"
gtk_tree_path_free :: ((Ptr NativeTreePath) -> (IO ()))
foreign import ccall unsafe "gtk_tree_path_new"
gtk_tree_path_new :: (IO (Ptr NativeTreePath))
foreign import ccall unsafe "gtk_tree_path_append_index"
gtk_tree_path_append_index :: ((Ptr NativeTreePath) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_tree_path_get_depth"
gtk_tree_path_get_depth :: ((Ptr NativeTreePath) -> (IO CInt))
foreign import ccall unsafe "gtk_tree_path_get_indices"
gtk_tree_path_get_indices :: ((Ptr NativeTreePath) -> (IO (Ptr CInt)))