module Media.Streaming.GStreamer.Core.Types (
module Media.Streaming.GStreamer.Core.Constants,
module Media.Streaming.GStreamer.Core.Hierarchy,
module Media.Streaming.GStreamer.Core.HierarchyBase,
module Media.Streaming.GStreamer.Core.MiniHierarchy,
module Media.Streaming.GStreamer.Core.MiniHierarchyBase,
cToFlags,
cFromFlags,
cToEnum,
cFromEnum,
FourCC,
Fraction,
FormatDefinition(..),
mkObjectGetFlags,
mkObjectSetFlags,
mkObjectUnsetFlags,
withObject,
peekObject,
takeObject,
giveObject,
PadDirection(..),
PadPresence(..),
PadLinkReturn(..),
FlowReturn(..),
ActivateMode(..),
StaticPadTemplate ,
staticPadTemplateGet,
State(..),
StateChangeReturn(..),
SeekFlags(..),
SeekType(..),
PluginFilter,
PluginFeatureFilter,
BusFunc,
BusSyncHandler,
BusSyncReply(..),
ClockTimeDiff,
ClockReturn(..),
ClockID(..),
withClockID,
takeClockID,
peekClockID,
IndexCertainty(..),
IndexEntry(..),
takeIndexEntry,
peekIndexEntry,
IndexEntryType(..),
IndexLookupMethod(..),
IndexFilter,
IndexAssociation(..),
AssocFlags(..),
withMiniObject,
peekMiniObject,
takeMiniObject,
giveMiniObject,
MiniObjectT(..),
askMiniObjectPtr,
runMiniObjectT,
marshalMiniObjectModify,
mkMiniObjectGetFlags,
mkMiniObjectGetFlagsM,
mkMiniObjectSetFlagsM,
mkMiniObjectUnsetFlagsM,
QueryType,
QueryTypeDefinition(..),
EventTypeFlags(..),
PtrIterator(..),
Iterator(..),
IteratorItem(..),
IteratorResult(..),
Iterable(..),
IteratorFilter,
IteratorFoldFunction,
withIterator,
takeIterator,
peekIterator,
Caps(..),
mkCaps,
unCaps,
withCaps,
takeCaps,
peekCaps,
giveCaps,
Structure(..),
StructureForeachFunc,
withStructure,
takeStructure,
peekStructure,
giveStructure,
StructureM(..),
StructureMRep,
TagList,
withTagList,
takeTagList,
peekTagList,
giveTagList,
Tag,
TagFlag,
TagMergeMode,
Segment(..),
) where
import Control.Monad ( liftM )
import Control.Monad.Reader
import Control.Monad.Trans
import Data.Ratio ( Ratio )
import System.Glib.FFI
import System.Glib.Flags
import System.Glib.GType
import System.Glib.GObject
import System.Glib.GValue
import System.Glib.UTFString
import Media.Streaming.GStreamer.Core.Constants
import Media.Streaming.GStreamer.Core.HierarchyBase
import Media.Streaming.GStreamer.Core.MiniHierarchyBase
import Media.Streaming.GStreamer.Core.Hierarchy
import Media.Streaming.GStreamer.Core.MiniHierarchy
type FourCC = Word32
type Fraction = Ratio Int
data ParseError = ParseErrorSyntax
| ParseErrorNoSuchElement
| ParseErrorNoSuchProperty
| ParseErrorLink
| ParseErrorCouldNotSetProperty
| ParseErrorEmptyBin
| ParseErrorEmpty
deriving (Enum,Eq,Show)
cToFlags :: (Integral int, Flags flags)
=> int
-> [flags]
cToFlags = toFlags . fromIntegral
cFromFlags :: (Integral int, Flags flags)
=> [flags]
-> int
cFromFlags = fromIntegral . fromFlags
cToEnum :: (Integral int, Enum enum)
=> int
-> enum
cToEnum = toEnum . fromIntegral
cFromEnum :: (Integral int, Enum enum)
=> enum
-> int
cFromEnum = fromIntegral . fromEnum
data FormatDefinition = FormatDefinition { formatValue :: FormatId
, formatNick :: String
, formatDescription :: String
, formatQuark :: Quark
} deriving (Eq, Show)
instance Storable FormatDefinition where
sizeOf = undefined
alignment = undefined
peek ptr =
do value <- liftM (FormatId . fromIntegral) $ (\ptr -> do {peekByteOff ptr 0 ::IO CInt}) ptr
nick <- (\ptr -> do {peekByteOff ptr 4 ::IO (Ptr CChar)}) ptr >>= peekUTFString
description <- (\ptr -> do {peekByteOff ptr 8 ::IO (Ptr CChar)}) ptr >>= peekUTFString
quark <- (\ptr -> do {peekByteOff ptr 12 ::IO CUInt}) ptr
return $ FormatDefinition value nick description quark
poke _ _ = undefined
instance Iterable FormatDefinition where
peekIterable = peek . castPtr
withIterable = with
withObject :: ObjectClass objectT
=> objectT
-> (Ptr objectT -> IO a)
-> IO a
withObject object action =
let objectFPtr = unObject $ toObject object
in withForeignPtr (castForeignPtr objectFPtr) action
peekObject, takeObject :: ObjectClass obj
=> Ptr obj
-> IO obj
peekObject cObject = do
liftM (unsafeCastGObject . GObject . castForeignPtr) $
do cObjectRef $ castPtr cObject
newForeignPtr (castPtr cObject) objectFinalizer
foreign import ccall unsafe "&gst_object_unref"
objectFinalizer :: FunPtr (Ptr () -> IO ())
foreign import ccall unsafe "gst_object_ref"
cObjectRef :: Ptr ()
-> IO (Ptr ())
takeObject cObject =
liftM (unsafeCastGObject . GObject . castForeignPtr) $
do cObjectUnfloat $ castPtr cObject
newForeignPtr (castPtr cObject) objectFinalizer
foreign import ccall unsafe "_hs_gst_object_unfloat"
cObjectUnfloat :: Ptr ()
-> IO ()
mkObjectGetFlags :: (ObjectClass objectT, Flags flagsT)
=> objectT
-> IO [flagsT]
mkObjectGetFlags object =
liftM cToFlags $
withObject (toObject object) cObjectGetFlags
foreign import ccall unsafe "_hs_gst_object_flags"
cObjectGetFlags :: Ptr Object
-> IO CUInt
mkObjectSetFlags :: (ObjectClass objectT, Flags flagsT)
=> objectT
-> [flagsT]
-> IO ()
mkObjectSetFlags object flags =
withObject (toObject object) $ \cObject ->
cObjectSetFlags cObject (fromIntegral $ fromFlags flags)
foreign import ccall unsafe "_hs_gst_object_flag_set"
cObjectSetFlags :: Ptr Object
-> CUInt
-> IO ()
mkObjectUnsetFlags :: (ObjectClass objectT, Flags flagsT)
=> objectT
-> [flagsT]
-> IO ()
mkObjectUnsetFlags object flags =
withObject (toObject object) $ \cObject ->
cObjectUnsetFlags cObject (fromIntegral $ fromFlags flags)
foreign import ccall unsafe "_hs_gst_object_flag_unset"
cObjectUnsetFlags :: Ptr Object
-> CUInt
-> IO ()
giveObject :: (ObjectClass obj, MonadIO m)
=> obj
-> (obj -> m a)
-> m a
giveObject obj action =
do liftIO $ withObject (toObject obj) $ gst_object_ref . castPtr
action obj
data PadDirection = PadUnknown
| PadSrc
| PadSink
deriving (Enum,Eq,Show)
data PadPresence = PadAlways
| PadSometimes
| PadRequest
deriving (Enum,Eq,Show)
data PadLinkReturn = PadLinkOk
| PadLinkWrongHierarchy
| PadLinkWasLinked
| PadLinkWrongDirection
| PadLinkNoformat
| PadLinkNosched
| PadLinkRefused
deriving (Eq,Show)
instance Enum PadLinkReturn where
fromEnum PadLinkOk = 0
fromEnum PadLinkWrongHierarchy = (1)
fromEnum PadLinkWasLinked = (2)
fromEnum PadLinkWrongDirection = (3)
fromEnum PadLinkNoformat = (4)
fromEnum PadLinkNosched = (5)
fromEnum PadLinkRefused = (6)
toEnum 0 = PadLinkOk
toEnum (1) = PadLinkWrongHierarchy
toEnum (2) = PadLinkWasLinked
toEnum (3) = PadLinkWrongDirection
toEnum (4) = PadLinkNoformat
toEnum (5) = PadLinkNosched
toEnum (6) = PadLinkRefused
toEnum unmatched = error ("PadLinkReturn.toEnum: Cannot match " ++ show unmatched)
succ PadLinkOk = PadLinkWrongHierarchy
succ PadLinkWrongHierarchy = PadLinkWasLinked
succ PadLinkWasLinked = PadLinkWrongDirection
succ PadLinkWrongDirection = PadLinkNoformat
succ PadLinkNoformat = PadLinkNosched
succ PadLinkNosched = PadLinkRefused
succ _ = undefined
pred PadLinkWrongHierarchy = PadLinkOk
pred PadLinkWasLinked = PadLinkWrongHierarchy
pred PadLinkWrongDirection = PadLinkWasLinked
pred PadLinkNoformat = PadLinkWrongDirection
pred PadLinkNosched = PadLinkNoformat
pred PadLinkRefused = PadLinkNosched
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x PadLinkRefused
enumFromThen _ _ = error "Enum PadLinkReturn: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum PadLinkReturn: enumFromThenTo not implemented"
data FlowReturn = FlowCustomSuccess2
| FlowCustomSuccess1
| FlowCustomSuccess
| FlowResend
| FlowOk
| FlowNotLinked
| FlowWrongState
| FlowUnexpected
| FlowNotNegotiated
| FlowError
| FlowNotSupported
| FlowCustomError
| FlowCustomError1
| FlowCustomError2
deriving (Eq,Show)
instance Enum FlowReturn where
fromEnum FlowCustomSuccess2 = 102
fromEnum FlowCustomSuccess1 = 101
fromEnum FlowCustomSuccess = 100
fromEnum FlowResend = 1
fromEnum FlowOk = 0
fromEnum FlowNotLinked = (1)
fromEnum FlowWrongState = (2)
fromEnum FlowUnexpected = (3)
fromEnum FlowNotNegotiated = (4)
fromEnum FlowError = (5)
fromEnum FlowNotSupported = (6)
fromEnum FlowCustomError = (100)
fromEnum FlowCustomError1 = (101)
fromEnum FlowCustomError2 = (102)
toEnum 102 = FlowCustomSuccess2
toEnum 101 = FlowCustomSuccess1
toEnum 100 = FlowCustomSuccess
toEnum 1 = FlowResend
toEnum 0 = FlowOk
toEnum (1) = FlowNotLinked
toEnum (2) = FlowWrongState
toEnum (3) = FlowUnexpected
toEnum (4) = FlowNotNegotiated
toEnum (5) = FlowError
toEnum (6) = FlowNotSupported
toEnum (100) = FlowCustomError
toEnum (101) = FlowCustomError1
toEnum (102) = FlowCustomError2
toEnum unmatched = error ("FlowReturn.toEnum: Cannot match " ++ show unmatched)
succ FlowCustomSuccess2 = FlowCustomSuccess1
succ FlowCustomSuccess1 = FlowCustomSuccess
succ FlowCustomSuccess = FlowResend
succ FlowResend = FlowOk
succ FlowOk = FlowNotLinked
succ FlowNotLinked = FlowWrongState
succ FlowWrongState = FlowUnexpected
succ FlowUnexpected = FlowNotNegotiated
succ FlowNotNegotiated = FlowError
succ FlowError = FlowNotSupported
succ FlowNotSupported = FlowCustomError
succ FlowCustomError = FlowCustomError1
succ FlowCustomError1 = FlowCustomError2
succ _ = undefined
pred FlowCustomSuccess1 = FlowCustomSuccess2
pred FlowCustomSuccess = FlowCustomSuccess1
pred FlowResend = FlowCustomSuccess
pred FlowOk = FlowResend
pred FlowNotLinked = FlowOk
pred FlowWrongState = FlowNotLinked
pred FlowUnexpected = FlowWrongState
pred FlowNotNegotiated = FlowUnexpected
pred FlowError = FlowNotNegotiated
pred FlowNotSupported = FlowError
pred FlowCustomError = FlowNotSupported
pred FlowCustomError1 = FlowCustomError
pred FlowCustomError2 = FlowCustomError1
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x FlowCustomError2
enumFromThen _ _ = error "Enum FlowReturn: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum FlowReturn: enumFromThenTo not implemented"
data ActivateMode = ActivateNone
| ActivatePush
| ActivatePull
deriving (Enum,Eq,Show)
instance Iterable Pad where
peekIterable = peekObject . castPtr
withIterable = withObject
type StaticPadTemplate = Ptr (())
staticPadTemplateGet :: StaticPadTemplate
-> IO PadTemplate
staticPadTemplateGet staticPadTemplate =
gst_static_pad_template_get staticPadTemplate >>= takeObject
data PluginError = PluginErrorModule
| PluginErrorDependencies
| PluginErrorNameMismatch
deriving (Enum,Eq,Show)
data SeekFlags = SeekFlagNone
| SeekFlagFlush
| SeekFlagAccurate
| SeekFlagKeyUnit
| SeekFlagSegment
| SeekFlagSkip
deriving (Eq,Bounded,Show)
instance Enum SeekFlags where
fromEnum SeekFlagNone = 0
fromEnum SeekFlagFlush = 1
fromEnum SeekFlagAccurate = 2
fromEnum SeekFlagKeyUnit = 4
fromEnum SeekFlagSegment = 8
fromEnum SeekFlagSkip = 16
toEnum 0 = SeekFlagNone
toEnum 1 = SeekFlagFlush
toEnum 2 = SeekFlagAccurate
toEnum 4 = SeekFlagKeyUnit
toEnum 8 = SeekFlagSegment
toEnum 16 = SeekFlagSkip
toEnum unmatched = error ("SeekFlags.toEnum: Cannot match " ++ show unmatched)
succ SeekFlagNone = SeekFlagFlush
succ SeekFlagFlush = SeekFlagAccurate
succ SeekFlagAccurate = SeekFlagKeyUnit
succ SeekFlagKeyUnit = SeekFlagSegment
succ SeekFlagSegment = SeekFlagSkip
succ _ = undefined
pred SeekFlagFlush = SeekFlagNone
pred SeekFlagAccurate = SeekFlagFlush
pred SeekFlagKeyUnit = SeekFlagAccurate
pred SeekFlagSegment = SeekFlagKeyUnit
pred SeekFlagSkip = SeekFlagSegment
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x SeekFlagSkip
enumFromThen _ _ = error "Enum SeekFlags: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum SeekFlags: enumFromThenTo not implemented"
instance Flags SeekFlags
data SeekType = SeekTypeNone
| SeekTypeCur
| SeekTypeSet
| SeekTypeEnd
deriving (Eq,Show)
instance Enum SeekType where
fromEnum SeekTypeNone = 0
fromEnum SeekTypeCur = 1
fromEnum SeekTypeSet = 2
fromEnum SeekTypeEnd = 3
toEnum 0 = SeekTypeNone
toEnum 1 = SeekTypeCur
toEnum 2 = SeekTypeSet
toEnum 3 = SeekTypeEnd
toEnum unmatched = error ("SeekType.toEnum: Cannot match " ++ show unmatched)
succ SeekTypeNone = SeekTypeCur
succ SeekTypeCur = SeekTypeSet
succ SeekTypeSet = SeekTypeEnd
succ _ = undefined
pred SeekTypeCur = SeekTypeNone
pred SeekTypeSet = SeekTypeCur
pred SeekTypeEnd = SeekTypeSet
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x SeekTypeEnd
enumFromThen _ _ = error "Enum SeekType: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum SeekType: enumFromThenTo not implemented"
data State = StateVoidPending
| StateNull
| StateReady
| StatePaused
| StatePlaying
deriving (Eq,Show)
instance Enum State where
fromEnum StateVoidPending = 0
fromEnum StateNull = 1
fromEnum StateReady = 2
fromEnum StatePaused = 3
fromEnum StatePlaying = 4
toEnum 0 = StateVoidPending
toEnum 1 = StateNull
toEnum 2 = StateReady
toEnum 3 = StatePaused
toEnum 4 = StatePlaying
toEnum unmatched = error ("State.toEnum: Cannot match " ++ show unmatched)
succ StateVoidPending = StateNull
succ StateNull = StateReady
succ StateReady = StatePaused
succ StatePaused = StatePlaying
succ _ = undefined
pred StateNull = StateVoidPending
pred StateReady = StateNull
pred StatePaused = StateReady
pred StatePlaying = StatePaused
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x StatePlaying
enumFromThen _ _ = error "Enum State: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum State: enumFromThenTo not implemented"
data StateChangeReturn = StateChangeFailure
| StateChangeSuccess
| StateChangeAsync
| StateChangeNoPreroll
deriving (Eq,Show)
instance Enum StateChangeReturn where
fromEnum StateChangeFailure = 0
fromEnum StateChangeSuccess = 1
fromEnum StateChangeAsync = 2
fromEnum StateChangeNoPreroll = 3
toEnum 0 = StateChangeFailure
toEnum 1 = StateChangeSuccess
toEnum 2 = StateChangeAsync
toEnum 3 = StateChangeNoPreroll
toEnum unmatched = error ("StateChangeReturn.toEnum: Cannot match " ++ show unmatched)
succ StateChangeFailure = StateChangeSuccess
succ StateChangeSuccess = StateChangeAsync
succ StateChangeAsync = StateChangeNoPreroll
succ _ = undefined
pred StateChangeSuccess = StateChangeFailure
pred StateChangeAsync = StateChangeSuccess
pred StateChangeNoPreroll = StateChangeAsync
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x StateChangeNoPreroll
enumFromThen _ _ = error "Enum StateChangeReturn: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum StateChangeReturn: enumFromThenTo not implemented"
instance Iterable Element where
peekIterable = peekObject . castPtr
withIterable = withObject
type PluginFilter = Plugin -> IO Bool
type PluginFeatureFilter = PluginFeature -> IO Bool
data BusSyncReply = BusDrop
| BusPass
| BusAsync
deriving (Eq,Show)
instance Enum BusSyncReply where
fromEnum BusDrop = 0
fromEnum BusPass = 1
fromEnum BusAsync = 2
toEnum 0 = BusDrop
toEnum 1 = BusPass
toEnum 2 = BusAsync
toEnum unmatched = error ("BusSyncReply.toEnum: Cannot match " ++ show unmatched)
succ BusDrop = BusPass
succ BusPass = BusAsync
succ _ = undefined
pred BusPass = BusDrop
pred BusAsync = BusPass
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x BusAsync
enumFromThen _ _ = error "Enum BusSyncReply: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum BusSyncReply: enumFromThenTo not implemented"
type BusFunc = Bus
-> Message
-> IO Bool
type BusSyncHandler = Bus
-> Message
-> IO BusSyncReply
type ClockTimeDiff = Int64
data ClockReturn = ClockOk
| ClockEarly
| ClockUnscheduled
| ClockBusy
| ClockBadtime
| ClockError
| ClockUnsupported
| ClockDone
deriving (Eq,Show)
instance Enum ClockReturn where
fromEnum ClockOk = 0
fromEnum ClockEarly = 1
fromEnum ClockUnscheduled = 2
fromEnum ClockBusy = 3
fromEnum ClockBadtime = 4
fromEnum ClockError = 5
fromEnum ClockUnsupported = 6
fromEnum ClockDone = 7
toEnum 0 = ClockOk
toEnum 1 = ClockEarly
toEnum 2 = ClockUnscheduled
toEnum 3 = ClockBusy
toEnum 4 = ClockBadtime
toEnum 5 = ClockError
toEnum 6 = ClockUnsupported
toEnum 7 = ClockDone
toEnum unmatched = error ("ClockReturn.toEnum: Cannot match " ++ show unmatched)
succ ClockOk = ClockEarly
succ ClockEarly = ClockUnscheduled
succ ClockUnscheduled = ClockBusy
succ ClockBusy = ClockBadtime
succ ClockBadtime = ClockError
succ ClockError = ClockUnsupported
succ ClockUnsupported = ClockDone
succ _ = undefined
pred ClockEarly = ClockOk
pred ClockUnscheduled = ClockEarly
pred ClockBusy = ClockUnscheduled
pred ClockBadtime = ClockBusy
pred ClockError = ClockBadtime
pred ClockUnsupported = ClockError
pred ClockDone = ClockUnsupported
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x ClockDone
enumFromThen _ _ = error "Enum ClockReturn: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum ClockReturn: enumFromThenTo not implemented"
newtype ClockID = ClockID (ForeignPtr (ClockID))
withClockID :: ClockID
-> (Ptr ClockID -> IO a)
-> IO a
withClockID (ClockID clockID) = withForeignPtr clockID
takeClockID, peekClockID :: Ptr ClockID
-> IO ClockID
takeClockID clockIDPtr =
liftM ClockID $ newForeignPtr clockIDPtr clockIDFinalizer
peekClockID clockIDPtr =
do gst_clock_id_ref $ castPtr clockIDPtr
takeClockID clockIDPtr
foreign import ccall unsafe "&gst_clock_id_unref"
clockIDFinalizer :: FunPtr (Ptr ClockID -> IO ())
data IndexCertainty = IndexUnknown
| IndexCertain
| IndexFuzzy
deriving (Enum,Eq,Show)
data IndexEntryType = IndexEntryId
| IndexEntryAssociation
| IndexEntryObject
| IndexEntryFormat
deriving (Enum,Eq,Show)
data IndexLookupMethod = IndexLookupExact
| IndexLookupBefore
| IndexLookupAfter
deriving (Enum,Eq,Show)
newtype IndexEntry = IndexEntry (ForeignPtr (IndexEntry))
takeIndexEntry :: Ptr IndexEntry
-> IO IndexEntry
takeIndexEntry ptr =
liftM IndexEntry $ newForeignPtr ptr indexEntryFinalizer
foreign import ccall unsafe "&gst_index_entry_free"
indexEntryFinalizer :: FunPtr (Ptr IndexEntry -> IO ())
peekIndexEntry :: Ptr IndexEntry
-> IO IndexEntry
peekIndexEntry ptr =
(liftM IndexEntry $ newForeignPtr_ ptr) >>=
(\(IndexEntry arg1) -> withForeignPtr arg1 $ \argPtr1 ->gst_index_entry_copy argPtr1) >>=
takeIndexEntry
type IndexFilter = Index
-> IndexEntry
-> IO Bool
data IndexAssociation = IndexAssociation Format Int64
deriving (Eq, Show)
instance Storable IndexAssociation where
sizeOf _ = 12
alignment _ = alignment (undefined :: CString)
peek ptr =
do format <- (\ptr -> do {peekByteOff ptr 0 ::IO CInt}) ptr
value <- (\ptr -> do {peekByteOff ptr 4 ::IO CLLong}) ptr
return $ IndexAssociation (toFormat $ fromIntegral format) (fromIntegral value)
poke ptr (IndexAssociation format value) =
do (\ptr val -> do {pokeByteOff ptr 0 (val::CInt)}) ptr $ fromIntegral (fromFormat format)
(\ptr val -> do {pokeByteOff ptr 4 (val::CLLong)}) ptr $ fromIntegral value
data AssocFlags = AssociationFlagNone
| AssociationFlagKeyUnit
| AssociationFlagDeltaUnit
| AssociationFlagLast
deriving (Eq,Bounded,Show)
instance Enum AssocFlags where
fromEnum AssociationFlagNone = 0
fromEnum AssociationFlagKeyUnit = 1
fromEnum AssociationFlagDeltaUnit = 2
fromEnum AssociationFlagLast = 256
toEnum 0 = AssociationFlagNone
toEnum 1 = AssociationFlagKeyUnit
toEnum 2 = AssociationFlagDeltaUnit
toEnum 256 = AssociationFlagLast
toEnum unmatched = error ("AssocFlags.toEnum: Cannot match " ++ show unmatched)
succ AssociationFlagNone = AssociationFlagKeyUnit
succ AssociationFlagKeyUnit = AssociationFlagDeltaUnit
succ AssociationFlagDeltaUnit = AssociationFlagLast
succ _ = undefined
pred AssociationFlagKeyUnit = AssociationFlagNone
pred AssociationFlagDeltaUnit = AssociationFlagKeyUnit
pred AssociationFlagLast = AssociationFlagDeltaUnit
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x AssociationFlagLast
enumFromThen _ _ = error "Enum AssocFlags: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum AssocFlags: enumFromThenTo not implemented"
instance Flags AssocFlags
withMiniObject :: MiniObjectClass miniObjectT
=> miniObjectT
-> (Ptr miniObjectT -> IO a)
-> IO a
withMiniObject miniObject action =
let miniObjectFPtr = unMiniObject $ toMiniObject miniObject
in withForeignPtr (castForeignPtr miniObjectFPtr) action
takeMiniObject, peekMiniObject :: (MiniObjectClass obj)
=> Ptr obj
-> IO obj
peekMiniObject cMiniObject =
do cMiniObjectRef $ castPtr cMiniObject
takeMiniObject cMiniObject
foreign import ccall unsafe "gst_mini_object_ref"
cMiniObjectRef :: Ptr ()
-> IO (Ptr ())
takeMiniObject cMiniObject =
do cMiniObjectMakeReadOnly $ castPtr cMiniObject
object <- newForeignPtr (castPtr cMiniObject) miniObjectFinalizer
return $ unsafeCastMiniObject $ MiniObject $ castForeignPtr object
foreign import ccall unsafe "&gst_mini_object_unref"
miniObjectFinalizer :: FunPtr (Ptr () -> IO ())
foreign import ccall unsafe "_hs_gst_mini_object_make_read_only"
cMiniObjectMakeReadOnly :: Ptr MiniObject
-> IO ()
giveMiniObject :: (MiniObjectClass obj, MonadIO m)
=> obj
-> (obj -> m a)
-> m a
giveMiniObject obj action =
do liftIO $ (\(MiniObject arg1) -> withForeignPtr arg1 $ \argPtr1 ->gst_mini_object_ref argPtr1) (toMiniObject obj)
action obj
newtype (MiniObjectClass miniObjectT, Monad m) =>
MiniObjectT miniObjectT m a =
MiniObjectT (ReaderT (Ptr miniObjectT) m a)
deriving (Functor, Monad, MonadTrans)
instance (MiniObjectClass miniObjectT, Monad m, MonadIO m) =>
MonadIO (MiniObjectT miniObjectT m) where
liftIO = MiniObjectT . liftIO
askMiniObjectPtr :: (MiniObjectClass miniObjectT, Monad m)
=> MiniObjectT miniObjectT m (Ptr miniObjectT)
askMiniObjectPtr = MiniObjectT $ ask
runMiniObjectT :: (MiniObjectClass miniObjectT, Monad m)
=> MiniObjectT miniObjectT m a
-> (Ptr miniObjectT)
-> m a
runMiniObjectT (MiniObjectT action) = runReaderT action
marshalMiniObjectModify :: (MiniObjectClass miniObjectT, MonadIO m)
=> m (Ptr miniObjectT)
-> MiniObjectT miniObjectT m a
-> m (miniObjectT, a)
marshalMiniObjectModify mkMiniObject action =
do ptr' <- mkMiniObject
ptr <- liftIO $ liftM castPtr $ gst_mini_object_make_writable $ castPtr ptr'
result <- runMiniObjectT action ptr
object <- liftIO $ takeMiniObject ptr
return (object, result)
where _ = (\(MiniObject arg1) -> withForeignPtr arg1 $ \argPtr1 ->gst_mini_object_make_writable argPtr1)
mkMiniObjectGetFlags :: (MiniObjectClass miniObjectT, Flags flagsT)
=> miniObjectT
-> [flagsT]
mkMiniObjectGetFlags miniObject =
cToFlags $ unsafePerformIO $
withMiniObject (toMiniObject miniObject) cMiniObjectGetFlags
foreign import ccall unsafe "_hs_gst_mini_object_flags"
cMiniObjectGetFlags :: Ptr MiniObject
-> IO CUInt
mkMiniObjectGetFlagsM :: (MiniObjectClass miniObjectT, Flags flagsT, MonadIO m)
=> MiniObjectT miniObjectT m [flagsT]
mkMiniObjectGetFlagsM = do
ptr <- askMiniObjectPtr
liftIO $ liftM cToFlags $ cMiniObjectGetFlags $ castPtr ptr
mkMiniObjectSetFlagsM :: (MiniObjectClass miniObjectT, Flags flagsT, MonadIO m)
=> [flagsT]
-> MiniObjectT miniObjectT m ()
mkMiniObjectSetFlagsM flags = do
ptr <- askMiniObjectPtr
liftIO $ cMiniObjectSetFlags (castPtr ptr) $ cFromFlags flags
foreign import ccall unsafe "_hs_gst_mini_object_flag_set"
cMiniObjectSetFlags :: Ptr MiniObject
-> CUInt
-> IO ()
mkMiniObjectUnsetFlagsM :: (MiniObjectClass miniObjectT, Flags flagsT, MonadIO m)
=> [flagsT]
-> MiniObjectT miniObjectT m ()
mkMiniObjectUnsetFlagsM flags = do
ptr <- askMiniObjectPtr
liftIO $ cMiniObjectUnsetFlags (castPtr ptr) $ cFromFlags flags
foreign import ccall unsafe "_hs_gst_mini_object_flag_unset"
cMiniObjectUnsetFlags :: Ptr MiniObject
-> CUInt
-> IO ()
type QueryType = (CInt)
data QueryTypeDefinition = QueryTypeDefinition {
queryTypeDefinitionValue :: QueryType,
queryTypeDefinitionNick :: String,
queryTypeDefinitionDescription :: String,
queryTypeDefinitionQuark :: Quark
} deriving (Eq, Show)
instance Storable QueryTypeDefinition where
sizeOf _ = 28
alignment _ = alignment (undefined :: CString)
peek ptr =
do value <- (\ptr -> do {peekByteOff ptr 0 ::IO CInt}) ptr
nick <- (\ptr -> do {peekByteOff ptr 4 ::IO (Ptr CChar)}) ptr >>= peekUTFString
description <- (\ptr -> do {peekByteOff ptr 8 ::IO (Ptr CChar)}) ptr >>= peekUTFString
quark <- (\ptr -> do {peekByteOff ptr 12 ::IO CUInt}) ptr
return $ QueryTypeDefinition value
nick
description
quark
poke _ _ = undefined
instance Iterable QueryTypeDefinition where
peekIterable = peek . castPtr
withIterable = with
data EventTypeFlags = EventTypeUpstream
| EventTypeDownstream
| EventTypeSerialized
deriving (Eq,Bounded,Show)
instance Enum EventTypeFlags where
fromEnum EventTypeUpstream = 1
fromEnum EventTypeDownstream = 2
fromEnum EventTypeSerialized = 4
toEnum 1 = EventTypeUpstream
toEnum 2 = EventTypeDownstream
toEnum 4 = EventTypeSerialized
toEnum unmatched = error ("EventTypeFlags.toEnum: Cannot match " ++ show unmatched)
succ EventTypeUpstream = EventTypeDownstream
succ EventTypeDownstream = EventTypeSerialized
succ _ = undefined
pred EventTypeDownstream = EventTypeUpstream
pred EventTypeSerialized = EventTypeDownstream
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x EventTypeSerialized
enumFromThen _ _ = error "Enum EventTypeFlags: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum EventTypeFlags: enumFromThenTo not implemented"
instance Flags EventTypeFlags
newtype PtrIterator = PtrIterator (ForeignPtr (PtrIterator))
withPtrIterator :: PtrIterator
-> (Ptr PtrIterator -> IO a)
-> IO a
withPtrIterator (PtrIterator cPtrIterator) = withForeignPtr cPtrIterator
takePtrIterator, peekPtrIterator :: Ptr PtrIterator
-> IO PtrIterator
takePtrIterator ptrIteratorPtr =
liftM PtrIterator $ newForeignPtr ptrIteratorPtr ptrIteratorFinalizer
peekPtrIterator ptrIteratorPtr =
liftM PtrIterator $ newForeignPtr_ ptrIteratorPtr
foreign import ccall unsafe "&gst_iterator_free"
ptrIteratorFinalizer :: FunPtr (Ptr PtrIterator -> IO ())
data IteratorItem = IteratorItemSkip
| IteratorItemPass
| IteratorItemEnd
deriving (Eq,Show)
instance Enum IteratorItem where
fromEnum IteratorItemSkip = 0
fromEnum IteratorItemPass = 1
fromEnum IteratorItemEnd = 2
toEnum 0 = IteratorItemSkip
toEnum 1 = IteratorItemPass
toEnum 2 = IteratorItemEnd
toEnum unmatched = error ("IteratorItem.toEnum: Cannot match " ++ show unmatched)
succ IteratorItemSkip = IteratorItemPass
succ IteratorItemPass = IteratorItemEnd
succ _ = undefined
pred IteratorItemPass = IteratorItemSkip
pred IteratorItemEnd = IteratorItemPass
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x IteratorItemEnd
enumFromThen _ _ = error "Enum IteratorItem: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum IteratorItem: enumFromThenTo not implemented"
data IteratorResult = IteratorDone
| IteratorOk
| IteratorResync
| IteratorError
deriving (Eq,Show)
instance Enum IteratorResult where
fromEnum IteratorDone = 0
fromEnum IteratorOk = 1
fromEnum IteratorResync = 2
fromEnum IteratorError = 3
toEnum 0 = IteratorDone
toEnum 1 = IteratorOk
toEnum 2 = IteratorResync
toEnum 3 = IteratorError
toEnum unmatched = error ("IteratorResult.toEnum: Cannot match " ++ show unmatched)
succ IteratorDone = IteratorOk
succ IteratorOk = IteratorResync
succ IteratorResync = IteratorError
succ _ = undefined
pred IteratorOk = IteratorDone
pred IteratorResync = IteratorOk
pred IteratorError = IteratorResync
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x IteratorError
enumFromThen _ _ = error "Enum IteratorResult: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum IteratorResult: enumFromThenTo not implemented"
mkIterator newPtrIterator cPtrIterator =
do ptrIterator <- newPtrIterator cPtrIterator
return $ Iterator ptrIterator
newtype Iterable a => Iterator a = Iterator PtrIterator
withIterator :: Iterator a
-> (Ptr PtrIterator -> IO a)
-> IO a
withIterator (Iterator ptrIterator) = withPtrIterator ptrIterator
takeIterator, peekIterator :: Ptr PtrIterator
-> IO (Iterator a)
takeIterator cPtrIterator = mkIterator takePtrIterator cPtrIterator
peekIterator cPtrIterator = mkIterator peekPtrIterator cPtrIterator
class Iterable a where
peekIterable :: Ptr ()
-> IO a
withIterable :: a
-> (Ptr a -> IO b)
-> IO b
type IteratorFilter itemT = itemT
-> IO Bool
type IteratorFoldFunction itemT accumT = itemT
-> accumT
-> IO (Bool, accumT)
newtype Caps = Caps (ForeignPtr (Caps))
mkCaps :: ForeignPtr Caps -> Caps
mkCaps = Caps
unCaps :: Caps -> ForeignPtr Caps
unCaps (Caps caps) = caps
withCaps :: Caps -> (Ptr Caps -> IO a) -> IO a
withCaps = withForeignPtr . unCaps
takeCaps, peekCaps :: Ptr Caps
-> IO Caps
takeCaps capsPtr =
liftM Caps $ newForeignPtr capsPtr capsFinalizer
peekCaps capsPtr =
cCapsRef capsPtr >>= takeCaps
foreign import ccall unsafe "gst_caps_ref"
cCapsRef :: Ptr Caps
-> IO (Ptr Caps)
giveCaps :: MonadIO m
=> Caps
-> (Caps -> m a)
-> m a
giveCaps caps action =
do liftIO $ (\(Caps arg1) -> withForeignPtr arg1 $ \argPtr1 ->gst_caps_ref argPtr1) caps
action caps
foreign import ccall unsafe "&gst_caps_unref"
capsFinalizer :: FunPtr (Ptr Caps -> IO ())
newtype Structure = Structure (ForeignPtr (Structure))
mkStructure :: ForeignPtr Structure -> Structure
mkStructure = Structure
unStructure :: Structure -> ForeignPtr Structure
unStructure (Structure structure) = structure
withStructure :: Structure -> (Ptr Structure -> IO a) -> IO a
withStructure = withForeignPtr . unStructure
mkNewStructure :: (Ptr Structure -> IO (ForeignPtr Structure))
-> Ptr Structure
-> IO Structure
mkNewStructure mkFP structurePtr =
do cStructureMakeImmutable structurePtr
liftM Structure $ mkFP structurePtr
foreign import ccall unsafe "_hs_gst_structure_make_immutable"
cStructureMakeImmutable :: Ptr Structure
-> IO ()
takeStructure, peekStructure :: Ptr Structure
-> IO Structure
takeStructure =
mkNewStructure $ flip newForeignPtr structureFinalizer
peekStructure ptr = do
copy <- gst_structure_copy ptr
takeStructure copy
where _ = (\(Structure arg1) -> withForeignPtr arg1 $ \argPtr1 ->gst_structure_copy argPtr1)
giveStructure :: MonadIO m
=> Structure
-> (Structure -> m a)
-> m a
giveStructure structure action =
do structure <- liftIO $ liftM Structure $
(\(Structure arg1) -> withForeignPtr arg1 $ \argPtr1 ->gst_structure_copy argPtr1) structure >>= newForeignPtr_
action structure
foreign import ccall unsafe "&gst_structure_free"
structureFinalizer :: FunPtr (Ptr Structure -> IO ())
type StructureForeachFunc = Quark
-> GValue
-> IO Bool
newtype StructureM a = StructureM (StructureMRep a)
type StructureMRep a = (Structure -> IO a)
instance Monad StructureM where
(StructureM aM) >>= fbM =
StructureM $ \structure ->
do a <- aM structure
let StructureM bM = fbM a
bM structure
return a = StructureM $ const $ return a
type TagList = Structure
mkTagList = mkStructure
unTagList = unStructure
withTagList = withStructure
takeTagList = takeStructure
peekTagList = takeStructure
giveTagList :: MonadIO m
=> TagList
-> (TagList -> m a)
-> m a
giveTagList = giveStructure
type Tag = String
data TagFlag = TagFlagUndefined
| TagFlagMeta
| TagFlagEncoded
| TagFlagDecoded
| TagFlagCount
deriving (Enum,Eq,Show)
data TagMergeMode = TagMergeUndefined
| TagMergeReplaceAll
| TagMergeReplace
| TagMergeAppend
| TagMergePrepend
| TagMergeKeep
| TagMergeKeepAll
| TagMergeCount
deriving (Enum,Eq,Show)
data Segment = Segment { segmentRate :: Double
, segmentAbsRate :: Double
, segmentFormat :: Format
, segmentFlags :: [SeekFlags]
, segmentStart :: Int64
, segmentStop :: Int64
, segmentTime :: Int64
, segmentAccum :: Int64
, segmentLastStop :: Int64
, segmentDuration :: Int64 }
deriving (Eq, Show)
instance Storable Segment where
sizeOf _ = fromIntegral cSegmentSizeof
alignment _ = alignment (undefined :: CString)
peek ptr =
do rate <- (\ptr -> do {peekByteOff ptr 0 ::IO CDouble}) ptr
absRate <- (\ptr -> do {peekByteOff ptr 8 ::IO CDouble}) ptr
format <- (\ptr -> do {peekByteOff ptr 16 ::IO CInt}) ptr
flags <- (\ptr -> do {peekByteOff ptr 20 ::IO CInt}) ptr
start <- (\ptr -> do {peekByteOff ptr 24 ::IO CLLong}) ptr
stop <- (\ptr -> do {peekByteOff ptr 32 ::IO CLLong}) ptr
time <- (\ptr -> do {peekByteOff ptr 40 ::IO CLLong}) ptr
accum <- (\ptr -> do {peekByteOff ptr 48 ::IO CLLong}) ptr
lastStop <- (\ptr -> do {peekByteOff ptr 56 ::IO CLLong}) ptr
duration <- (\ptr -> do {peekByteOff ptr 64 ::IO CLLong}) ptr
return $ Segment (realToFrac rate)
(realToFrac absRate)
(toFormat $ fromIntegral format)
(cToFlags flags)
(fromIntegral start)
(fromIntegral stop)
(fromIntegral time)
(fromIntegral accum)
(fromIntegral lastStop)
(fromIntegral duration)
poke ptr (Segment rate
absRate
format
flags
start
stop
time
accum
lastStop
duration) =
do gst_segment_init (castPtr ptr)
(fromIntegral $ fromFormat format)
(\ptr val -> do {pokeByteOff ptr 0 (val::CDouble)}) ptr $ realToFrac rate
(\ptr val -> do {pokeByteOff ptr 8 (val::CDouble)}) ptr $ realToFrac absRate
(\ptr val -> do {pokeByteOff ptr 16 (val::CInt)}) ptr $ fromIntegral (fromFormat format)
(\ptr val -> do {pokeByteOff ptr 20 (val::CInt)}) ptr $ fromIntegral $ fromFlags flags
(\ptr val -> do {pokeByteOff ptr 24 (val::CLLong)}) ptr $ fromIntegral start
(\ptr val -> do {pokeByteOff ptr 32 (val::CLLong)}) ptr $ fromIntegral stop
(\ptr val -> do {pokeByteOff ptr 40 (val::CLLong)}) ptr $ fromIntegral time
(\ptr val -> do {pokeByteOff ptr 48 (val::CLLong)}) ptr $ fromIntegral accum
(\ptr val -> do {pokeByteOff ptr 56 (val::CLLong)}) ptr $ fromIntegral lastStop
(\ptr val -> do {pokeByteOff ptr 64 (val::CLLong)}) ptr $ fromIntegral duration
foreign import ccall unsafe "_hs_gst_segment_sizeof"
cSegmentSizeof :: (CUInt)
foreign import ccall safe "gst_object_ref"
gst_object_ref :: ((Ptr ()) -> (IO (Ptr ())))
foreign import ccall safe "gst_static_pad_template_get"
gst_static_pad_template_get :: ((Ptr ()) -> (IO (Ptr PadTemplate)))
foreign import ccall safe "gst_clock_id_ref"
gst_clock_id_ref :: ((Ptr ()) -> (IO (Ptr ())))
foreign import ccall safe "gst_index_entry_copy"
gst_index_entry_copy :: ((Ptr IndexEntry) -> (IO (Ptr IndexEntry)))
foreign import ccall safe "gst_mini_object_ref"
gst_mini_object_ref :: ((Ptr MiniObject) -> (IO (Ptr MiniObject)))
foreign import ccall safe "gst_mini_object_make_writable"
gst_mini_object_make_writable :: ((Ptr MiniObject) -> (IO (Ptr MiniObject)))
foreign import ccall safe "gst_caps_ref"
gst_caps_ref :: ((Ptr Caps) -> (IO (Ptr Caps)))
foreign import ccall safe "gst_structure_copy"
gst_structure_copy :: ((Ptr Structure) -> (IO (Ptr Structure)))
foreign import ccall safe "gst_segment_init"
gst_segment_init :: ((Ptr ()) -> (CInt -> (IO ())))