{-# LANGUAGE ForeignFunctionInterface #-} -- | -- Module : Mac.QuickTime -- Maintainer : Yakov Z <> -- Stability : experimental -- module Mac.QuickTime ( ComponentResult, ImageDescriptionPtr, height, width, noErr, srcCopy, codecNormalQuality, bestSpeedCodec, videoMediaType, seqGrabRecord, k32ARGBPixelFormat, -- k24RGBPixelFormat, -- * Sequence Grabber SeqGrabComponent, SGDataProc, SGDataProcPtr, SGDataUPP, -- ** Configuring Sequence Grabber Components seqGrabComponentType, seqGrabDontMakeMovie, sGInitialize, sGNewChannel, mkSGDataProc, newSGDataUPP, sGSetDataProc, sGSetDataRef, sGSetGWorld, -- ** Controlling Sequence Grabber Components sGIdle, sGStartRecord, sGStop, -- ** Working with Channel Characteristics sGSetChannelBounds, sGGetChannelSampleDescription, sGSetChannelUsage, -- * Compression and Decompression MatrixRecord, GWorldPtr, ImageSequence, -- ** Managing Matricies rectMatrix, -- ** Working with Sequences decompressSequenceBegin, decompressSequenceFrameS, -- ** Supporing Functions qTNewGWorld, -- * Movie Manager -- ** Initializing the Movie Toolbox enterMovies, (), ) where import Foreign.Ptr import Foreign.C.Types import Foreign.Storable import Mac.Carbon import Mac.QuickDraw #include data MatrixRecord = MatrixRecord instance Storable MatrixRecord where sizeOf _ = #const sizeof(MatrixRecord) alignment _ = alignment (undefined :: CInt) -- ??? type ComponentResult = CLong type SeqGrabComponent = Ptr () type SGChannel = Ptr () type GWorldPtr = CGrafPtr -- | -- -- The sixth argument is the starting time of the data, in the channels time scale. -- type SGDataProc = SGChannel -> Ptr () -> CLong -> Ptr CLong -> CLong -> TimeValue -> CShort -> Ptr () -> IO OSErr {- MungGrabDataProc - the sequence grabber calls the data function whenever any of the grabbers channels write digitized data to the destination movie file. NOTE: We really mean any, if you have an audio and video channel then the DataProc will be called for either channel whenever data has been captured. Be sure to check which channel is being passed in. In this example we never create an audio channel so we know we're always dealing with video. This data function does two things, it first decompresses captured video data into an offscreen GWorld, draws some status information onto the frame then transfers the frame to an onscreen window. For more information refer to Inside Macintosh: QuickTime Components, page 5-120 c - the channel component that is writing the digitized data. p - a pointer to the digitized data. len - the number of bytes of digitized data. offset - a pointer to a field that may specify where you are to write the digitized data, and that is to receive a value indicating where you wrote the data. chRefCon - per channel reference constant specified using SGSetChannelRefCon. time - the starting time of the data, in the channels time scale. writeType - the type of write operation being performed. seqGrabWriteAppend - Append new data. seqGrabWriteReserve - Do not write data. Instead, reserve space for the amount of data specified in the len parameter. seqGrabWriteFill - Write data into the location specified by offset. Used to fill the space previously reserved with seqGrabWriteReserve. The Sequence Grabber may call the DataProc several times to fill a single reserved location. refCon - the reference constant you specified when you assigned your data function to the sequence grabber. -} type SGDataProcPtr = FunPtr SGDataProc type SGDataUPP = SGDataProcPtr type GWorldFlags = CULong type ImageSequence = CLong type ImageDescriptionPtr = Ptr ImageDescription type ImageDescriptionHandle = Ptr ImageDescriptionPtr data ImageDescription = ImageDescription { width :: CShort, height :: CShort } instance Storable ImageDescription where sizeOf _ = #const sizeof(ImageDescription) alignment _ = alignment (undefined :: CInt) -- ??? peek p = do width' <- (#peek ImageDescription, width) p height' <- (#peek ImageDescription, height) p return ImageDescription { width = width', height = height' } poke p (ImageDescription width' height') = do (#poke ImageDescription, width) p width' (#poke ImageDescription, height) p height' type RgnHandle = Ptr () type CodecFlags = CUShort type CodecQ = CUShort type Component = CULong data RGBColor = RGBColor { red :: CUShort, green :: CUShort, blue :: CUShort } instance Storable RGBColor where sizeOf _ = #const sizeof(RGBColor) alignment _ = alignment (undefined :: CInt) -- ??? peek p = do red' <- (#peek RGBColor, red) p green' <- (#peek RGBColor, green) p blue' <- (#peek RGBColor, blue) p return RGBColor { red = red', green = green', blue = blue' } () :: IO ComponentResult -> String -> IO () act msg = act >>= \err -> if err /= noErr then error (msg ++ ": " ++ (show err)) else return () noErr :: ComponentResult noErr = #const noErr seqGrabComponentType :: OSType seqGrabComponentType = #const SeqGrabComponentType seqGrabDontMakeMovie :: CLong seqGrabDontMakeMovie = #const seqGrabDontMakeMovie videoMediaType :: OSType videoMediaType = #const VideoMediaType seqGrabRecord :: CLong seqGrabRecord = #const seqGrabRecord k32ARGBPixelFormat, k24RGBPixelFormat :: OSType k32ARGBPixelFormat = #const k32ARGBPixelFormat k24RGBPixelFormat = #const k24RGBPixelFormat srcCopy :: CShort srcCopy = #const srcCopy codecNormalQuality :: CodecQ codecNormalQuality = #const codecNormalQuality bestSpeedCodec :: Component bestSpeedCodec = #const bestSpeedCodec foreign import ccall unsafe "SGStop" sGStop :: SeqGrabComponent -> IO ComponentResult foreign import ccall unsafe "SGInitialize" sGInitialize :: SeqGrabComponent -> IO ComponentResult foreign import ccall unsafe "SGSetDataRef" sGSetDataRef :: SeqGrabComponent -> Handle -> OSType -> CLong -> IO ComponentResult foreign import ccall unsafe "SGSetGWorld" sGSetGWorld :: SeqGrabComponent -> CGrafPtr -> GDHandle -> IO ComponentResult foreign import ccall unsafe "SGNewChannel" sGNewChannel :: SeqGrabComponent -> OSType -> Ptr SGChannel -> IO ComponentResult foreign import ccall unsafe "SGSetChannelBounds" sGSetChannelBounds :: SGChannel -> Ptr Rect -> IO ComponentResult foreign import ccall unsafe "SGSetChannelUsage" sGSetChannelUsage :: SGChannel -> CLong -> IO ComponentResult foreign import ccall unsafe "SGStartRecord" sGStartRecord :: SeqGrabComponent -> IO ComponentResult -- | Provides processing time for sequence grabber components. -- -- After starting a preview operation, the application calls this function /as often as possible/. -- -- If your component returns a non-'noErr' result during a record operation, the application should call 'sGStop' so that the sequence grabber component can store the data it has collected. -- foreign import ccall safe "SGIdle" sGIdle :: SeqGrabComponent -> IO ComponentResult foreign import ccall "wrapper" mkSGDataProc :: SGDataProc -> IO SGDataProcPtr foreign import ccall unsafe "NewSGDataUPP" newSGDataUPP :: SGDataProcPtr -> IO SGDataUPP foreign import ccall unsafe "SGSetDataProc" sGSetDataProc :: SeqGrabComponent -> SGDataUPP -> Ptr () -> IO ComponentResult foreign import ccall unsafe "SGGetChannelSampleDescription" sGGetChannelSampleDescription :: SGChannel -> Handle -> IO ComponentResult -- | Creates a matrix that performs the translate and scale operation described by the relationship between two rectangles. foreign import ccall unsafe "RectMatrix" rectMatrix :: Ptr MatrixRecord -> Ptr Rect -> Ptr Rect -> IO () foreign import ccall unsafe "DecompressSequenceBegin" decompressSequenceBegin :: Ptr ImageSequence -> ImageDescriptionHandle -> CGrafPtr -> GDHandle -> Ptr Rect -> Ptr MatrixRecord -> CShort -> RgnHandle -> CodecFlags -> CodecQ -> Component -> IO OSErr foreign import ccall unsafe "DecompressSequenceFrameS" decompressSequenceFrameS :: ImageSequence -> Ptr () -> CLong -> CodecFlags -> Ptr CodecFlags -> Ptr () -> IO OSErr -- | Creates an offscreen graphics world that may have non-Macintosh pixel format. -- -- Related Sample Code -- -- * VideoProcessing foreign import ccall unsafe "QTNewGWorld" qTNewGWorld :: Ptr GWorldPtr -> OSType -> Ptr Rect -> Ptr () -> Ptr () -> GWorldFlags -> IO ComponentResult -- | Initializes the Movie Toolbox and creates a private storage area for your application. -- -- Be sure to check the value returned by this function before using any other facilities of the Movie Toolbox. foreign import ccall unsafe "EnterMovies" enterMovies :: IO OSErr