{-# LANGUAGE ForeignFunctionInterface, TypeFamilies #-} module Graphics.QML.DataModel.Internal.FFI.Types where import Foreign.C.Types import Foreign.Storable import Foreign.Ptr import Graphics.QML.Marshal -- |Identifier of a HaskellModel delegate handle. newtype HmDelegateHandle = HmDelegateHandle CInt -- |Pointer to a QVariant type. newtype QtVariant = QtVariant (Ptr CChar) -- |Identifier of a column type. newtype HmColumnType = HmColumnType CInt deriving (Eq, Show) instance Marshal HmDelegateHandle where type MarshalMode HmDelegateHandle c d = ModeBidi c marshaller = bidiMarshaller (\i -> HmDelegateHandle (CInt i)) (\(HmDelegateHandle (CInt i)) -> i) -- |Used by QML to query the number of rows in a model. type RowCountCallback = IO CInt -- |Used by QML to query the number of columns in a model. type ColumnCountCallback = IO CInt -- |Used by QML to obtain a row at the given index. type DataCallback = CInt -> CInt -> IO QtVariant -- |Used by QML to obtain the name of the column at the given index. type HeaderDataCallback = CInt -> IO QtVariant -- |C struct storing HaskellModel callbacks. data HmCallbacks = HmCallbacks { rowCountCallback :: FunPtr RowCountCallback , columnCountCallback :: FunPtr ColumnCountCallback , dataCallback :: FunPtr DataCallback , headerDataCallback :: FunPtr HeaderDataCallback } #include "types.h" instance Storable HmCallbacks where sizeOf _ = #{size HaskellModelCallbacks} alignment _ = alignment (undefined :: CInt) poke ptr hmc = do #{poke HaskellModelCallbacks, rowCountCb } ptr $ rowCountCallback hmc #{poke HaskellModelCallbacks, columnCountCb} ptr $ columnCountCallback hmc #{poke HaskellModelCallbacks, dataCb } ptr $ dataCallback hmc #{poke HaskellModelCallbacks, headerDataCb } ptr $ headerDataCallback hmc peek ptr = HmCallbacks <$> (#peek HaskellModelCallbacks, rowCountCb ) ptr <*> (#peek HaskellModelCallbacks, columnCountCb) ptr <*> (#peek HaskellModelCallbacks, dataCb ) ptr <*> (#peek HaskellModelCallbacks, headerDataCb ) ptr