File: Adapter.chs

package info (click to toggle)
haskell-gstreamer 0.12.1-1
  • links: PTS, VCS
  • area: main
  • in suites: wheezy
  • size: 720 kB
  • sloc: haskell: 635; ansic: 116; makefile: 11; sh: 7
file content (191 lines) | stat: -rw-r--r-- 5,762 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
{-# LANGUAGE CPP #-}
--  GIMP Toolkit (GTK) Binding for Haskell: binding to gstreamer -*-haskell-*-
--
--  Author : Peter Gavin
--  Created: 1-Apr-2007
--
--  Copyright (c) 2007 Peter Gavin
--
--  This library is free software: you can redistribute it and/or
--  modify it under the terms of the GNU Lesser General Public License
--  as published by the Free Software Foundation, either version 3 of
--  the License, or (at your option) any later version.
--  
--  This library is distributed in the hope that it will be useful,
--  but WITHOUT ANY WARRANTY; without even the implied warranty of
--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
--  Lesser General Public License for more details.
--  
--  You should have received a copy of the GNU Lesser General Public
--  License along with this program.  If not, see
--  <http://www.gnu.org/licenses/>.
--  
--  GStreamer, the C library which this Haskell library depends on, is
--  available under LGPL Version 2. The documentation included with
--  this library is based on the original GStreamer documentation.
--  
-- | Maintainer  : gtk2hs-devel@lists.sourceforge.net
--   Stability   : alpha
--   Portability : portable (depends on GHC)
module Media.Streaming.GStreamer.Base.Adapter (
  
  Adapter,
  AdapterClass,
  castToAdapter,
  gTypeAdapter,

  adapterNew,
  adapterClear,
  adapterPush,
#if __GLASGOW_HASKELL__ >= 606
  adapterPeek,
#if GST_CHECK_VERSION(0,10,12)
  adapterCopy,
  adapterCopyInto,
#endif
#endif
  adapterFlush,
  adapterAvailable,
  adapterAvailableFast,
#if __GLASGOW_HASKELL__ >= 606
  adapterTake,
#endif
  adapterTakeBuffer
  
  ) where

import Control.Monad (liftM)

#if __GLASGOW_HASKELL__ >= 606
#if __GLASGOW_HASKELL__ < 608
#define OLD_BYTESTRING
#endif

import qualified Data.ByteString as BS
#ifdef OLD_BYTESTRING
import qualified Data.ByteString.Base as BS
#else
import qualified Data.ByteString.Unsafe as BS
import qualified Data.ByteString.Internal as BS
#endif
#endif

{#import Media.Streaming.GStreamer.Base.Types#}
import System.Glib.FFI
import System.Glib.GObject
import System.Glib.Flags
import System.Glib.Attributes
{#import System.Glib.Properties#}

{# context lib = "gstreamer" prefix = "gst" #}

adapterNew :: IO Adapter
adapterNew =
    wrapNewGObject mkAdapter {# call adapter_new #}

adapterClear :: AdapterClass adapterT
             => adapterT
             -> IO ()
adapterClear =
    {# call adapter_clear #} . toAdapter

adapterPush :: (AdapterClass adapterT, BufferClass bufferT)
            => adapterT
            -> bufferT
            -> IO ()
adapterPush adapter buffer =
    {# call adapter_push #} (toAdapter adapter) (toBuffer buffer)

#if __GLASGOW_HASKELL__ >= 606
adapterPeek :: AdapterClass adapterT
            => adapterT
            -> Word
            -> IO (Maybe BS.ByteString)
adapterPeek adapter size =
    do ptr <- {# call adapter_peek #} (toAdapter adapter) (fromIntegral size)
       if ptr == nullPtr
           then return Nothing
           else liftM Just $
#ifdef OLD_BYTESTRING
                BS.copyCStringLen
#else
                BS.packCStringLen
#endif
                     (castPtr ptr, fromIntegral size)

#if GST_CHECK_VERSION(0,10,12)
adapterCopy :: AdapterClass adapterT
            => adapterT
            -> Word
            -> Word
            -> IO BS.ByteString
adapterCopy adapter offset size = do
    BS.create (fromIntegral size) $ \dest ->
        {# call adapter_copy #} (toAdapter adapter)
                                (castPtr dest)
                                (fromIntegral offset)
                                (fromIntegral size)

adapterCopyInto :: AdapterClass adapterT
                => adapterT
                -> BS.ByteString
                -> Word
                -> IO ()
adapterCopyInto adapter dest offset =
    BS.useAsCStringLen dest $ \(destPtr, size) ->
        {# call adapter_copy #} (toAdapter adapter)
                                (castPtr destPtr)
                                (fromIntegral offset)
                                (fromIntegral size)
#endif
#endif

adapterFlush :: AdapterClass adapterT
             => adapterT
             -> Word
             -> IO ()
adapterFlush adapter flush =
    {# call adapter_flush #} (toAdapter adapter) $ fromIntegral flush

adapterAvailable :: AdapterClass adapterT
                 => adapterT
                 -> IO Word
adapterAvailable adapter =
    liftM fromIntegral $
        {# call adapter_available #} $ toAdapter adapter

adapterAvailableFast :: AdapterClass adapterT
                     => adapterT
                     -> IO Word
adapterAvailableFast adapter =
    liftM fromIntegral $
        {# call adapter_available_fast #} $ toAdapter adapter

#if __GLASGOW_HASKELL__ >= 606
adapterTake :: AdapterClass adapterT
            => adapterT
            -> Word
            -> IO (Maybe BS.ByteString)
adapterTake adapter nBytes =
    do ptr <- {# call adapter_take #} (toAdapter adapter)
                                      (fromIntegral nBytes)
       if ptr == nullPtr
          then do fPtr <- newForeignPtr (castPtr ptr) gFreePtr
                  return $ Just $
                      BS.fromForeignPtr (castForeignPtr fPtr)
#ifndef OLD_BYTESTRING
                                        0
#endif
                                        (fromIntegral nBytes)
          else return Nothing
foreign import ccall unsafe "&g_free"
    gFreePtr :: FunPtr (Ptr () -> IO ())
#endif

adapterTakeBuffer :: AdapterClass adapterT
                  => adapterT
                  -> Word
                  -> IO (Maybe Buffer)
adapterTakeBuffer adapter nBytes =
    {# call adapter_take_buffer #} (toAdapter adapter) (fromIntegral nBytes) >>=
        maybePeek takeMiniObject