{-# LINE 1 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
{-# OPTIONS_HADDOCK hide #-}
{-# LINE 2 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
--  GIMP Toolkit (GTK) Binding for Haskell: binding to gstreamer -*-haskell-*-


{-# LINE 5 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 6 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

--
--  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.

-- #hide
  
-- | Maintainer  : gtk2hs-devel@lists.sourceforge.net
--   Stability   : alpha
--   Portability : portable (depends on GHC)
module Media.Streaming.GStreamer.Core.Constants where

import Data.Int
import Data.Word
import System.Glib.Flags

-- | A time value in nanoseconds.
type ClockTime = Word64

-- | The undefined 'ClockTime' value.
clockTimeNone :: ClockTime
clockTimeNone = 4294967295
{-# LINE 48 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

second, msecond, usecond, nsecond :: ClockTime
-- | One second as a 'ClockTime' value.
second  = 1000000000
{-# LINE 52 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
-- | One millisecond as a 'ClockTime' value.
msecond = 1000000
{-# LINE 54 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
-- | One microsecond as a 'ClockTime' value.
usecond = 1000
{-# LINE 56 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
-- | One nanosecond as a 'ClockTime' value.
nsecond = 1
{-# LINE 58 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

-- | The type for buffer offsets.
type BufferOffset = Word64
-- | The undefined 'BufferOffset' value.
bufferOffsetNone :: BufferOffset
bufferOffsetNone = 4294967295
{-# LINE 64 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

-- | A format identifier.
newtype FormatId = FormatId Word32
{-# LINE 67 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    deriving (Eq, Ord, Show)

-- | An enumeration of standard predefined formats.
data Format = FormatUndefined     -- ^ no format
            | FormatDefault       -- ^ the default format of the pad or element; this can be, e.g., samples for raw audio
            | FormatBytes         -- ^ bytes
            | FormatTime          -- ^ time in nanoseconds
            | FormatBuffers       -- ^ buffers
            | FormatPercent       -- ^ percentage of stream
            | FormatUser FormatId -- ^ a user defined format
              deriving (Eq, Ord, Show)
toFormat :: Word32 -> Format
{-# LINE 79 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
toFormat n | n == 0 = FormatUndefined
{-# LINE 80 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
           | n == 1   = FormatDefault
{-# LINE 81 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
           | n == 2     = FormatBytes
{-# LINE 82 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
           | n == 3      = FormatTime
{-# LINE 83 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
           | n == 4   = FormatBuffers
{-# LINE 84 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
           | n == 5   = FormatPercent
{-# LINE 85 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
           | otherwise                          = FormatUser (FormatId n)
fromFormat :: Format -> Word32
{-# LINE 87 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
fromFormat FormatUndefined = 0
{-# LINE 88 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
fromFormat FormatDefault   = 1
{-# LINE 89 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
fromFormat FormatBytes     = 2
{-# LINE 90 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
fromFormat FormatTime      = 3
{-# LINE 91 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
fromFormat FormatBuffers   = 4
{-# LINE 92 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
fromFormat FormatPercent   = 5
{-# LINE 93 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
fromFormat (FormatUser (FormatId id)) = id

-- | The format value for 'FormatPercent' is between 0 and this value.
formatPercentMax :: Int64
formatPercentMax = 1000000
{-# LINE 98 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

-- | The value used to scale down the reported 'FormatPercent' format
--   value to its real value.
formatPercentScale :: Int64
formatPercentScale = 10000
{-# LINE 103 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

-- | The flags that an 'Object' may have.
data ObjectFlags = ObjectDisposing  -- ^ The object has been
                                    --   destroyed, don't use it any
                                    --   more.
                   deriving (Bounded, Show)
instance Enum ObjectFlags where
    toEnum n | n == 1 = ObjectDisposing
{-# LINE 111 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum ObjectDisposing = 1
{-# LINE 112 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
instance Flags ObjectFlags

-- | The flags that a 'Pad' may have.
data PadFlags = PadBlocked   -- ^ dataflow on the pad is blocked
              | PadFlushing  -- ^ the pad is refusing buffers
              | PadInGetCaps -- ^ 'padGetCaps' is executing
              | PadInSetCaps -- ^ 'padSetCaps' is executing

{-# LINE 120 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
              | PadBlocking  -- ^ the pad is blocking on a buffer or event

{-# LINE 122 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
                deriving (Eq, Bounded, Show)
instance Enum PadFlags where
    toEnum n | n == 16    = PadBlocked
{-# LINE 125 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 32   = PadFlushing
{-# LINE 126 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 64 = PadInGetCaps
{-# LINE 127 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 128 = PadInSetCaps
{-# LINE 128 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 129 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 256   = PadBlocking
{-# LINE 130 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 131 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum PadBlocked   = 16
{-# LINE 132 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum PadFlushing  = 32
{-# LINE 133 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum PadInGetCaps = 64
{-# LINE 134 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum PadInSetCaps = 128
{-# LINE 135 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 136 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum PadBlocking  = 256
{-# LINE 137 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 138 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
instance Flags PadFlags

-- | The flags that an 'Element' may have.
data ElementFlags = ElementLockedState -- ^ parent state changes are ignored
                  | ElementIsSink      -- ^ the element is a sink
                  | ElementUnparenting -- ^ child is being removed
                                       --   from the parent bin
                    deriving (Eq, Bounded, Show)
instance Enum ElementFlags where
    toEnum n | n == 16 = ElementLockedState
{-# LINE 148 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 32      = ElementIsSink
{-# LINE 149 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 64  = ElementUnparenting
{-# LINE 150 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum ElementLockedState = 16
{-# LINE 151 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum ElementIsSink      = 32
{-# LINE 152 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum ElementUnparenting = 64
{-# LINE 153 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
instance Flags ElementFlags

-- | The different state changes that are passed to the state change
--   functions of 'Element's.
data StateChange = StateChangeNullToReady     -- ^ state change from 'StateNull' to 'StateReady'
                 | StateChangeReadyToPaused   -- ^ state change from 'StateReady' to 'StatePaused'
                 | StateChangePausedToPlaying -- ^ state change from 'StatePaused' to 'StatePlaying'
                 | StateChangePlayingToPaused -- ^ state change from 'StatePlaying' to 'StatePaused'
                 | StateChangePausedToReady   -- ^ state change from 'StatePaused' to 'StateReady'
                 | StateChangeReadyToNull     -- ^ state change from 'StateReady' to 'StateNull'
                   deriving (Eq, Show)
instance Enum StateChange where
    toEnum n | n == 10     = StateChangeNullToReady
{-# LINE 166 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 19   = StateChangeReadyToPaused
{-# LINE 167 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 28 = StateChangePausedToPlaying
{-# LINE 168 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 35 = StateChangePlayingToPaused
{-# LINE 169 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 26   = StateChangePausedToReady
{-# LINE 170 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 17     = StateChangeReadyToNull
{-# LINE 171 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    
    fromEnum StateChangeNullToReady     = 10
{-# LINE 173 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum StateChangeReadyToPaused   = 19
{-# LINE 174 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum StateChangePausedToPlaying = 28
{-# LINE 175 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum StateChangePlayingToPaused = 35
{-# LINE 176 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum StateChangePausedToReady   = 26
{-# LINE 177 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum StateChangeReadyToNull     = 17
{-# LINE 178 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

-- | The flags that a 'Bus' may have.
data BusFlags = BusFlushing -- ^ the bus is currently dropping all messages
                deriving (Eq, Bounded, Show)
instance Enum BusFlags where
    toEnum n | n == 16 = BusFlushing
{-# LINE 184 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum BusFlushing = 16
{-# LINE 185 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
instance Flags BusFlags

-- | The flags that a 'Clock' may have.
data ClockFlags = ClockCanDoSingleSync    -- ^ the clock can do a single sync timeout request
                | ClockCanDoSingleAsync   -- ^ the clock can do a single async timeout request
                | ClockCanDoPeriodicSync  -- ^ the clock can do periodic sync timeout requests
                | ClockCanDoPeriodicAsync -- ^ the clock can do periodic async timeout requests
                | ClockCanSetResolution   -- ^ the clock's resolution can be changed
                | ClockCanSetMaster       -- ^ the clock can be slaved to a master clock
                  deriving (Eq, Bounded, Show)
instance Enum ClockFlags where
    toEnum n | n == 16    = ClockCanDoSingleSync
{-# LINE 197 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 32   = ClockCanDoSingleAsync
{-# LINE 198 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 64  = ClockCanDoPeriodicSync
{-# LINE 199 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 128 = ClockCanDoPeriodicAsync
{-# LINE 200 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 256    = ClockCanSetResolution
{-# LINE 201 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 512        = ClockCanSetMaster
{-# LINE 202 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    
    fromEnum ClockCanDoSingleSync    = 16
{-# LINE 204 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum ClockCanDoSingleAsync   = 32
{-# LINE 205 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum ClockCanDoPeriodicSync  = 64
{-# LINE 206 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum ClockCanDoPeriodicAsync = 128
{-# LINE 207 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum ClockCanSetResolution   = 256
{-# LINE 208 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum ClockCanSetMaster       = 512
{-# LINE 209 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
instance Flags ClockFlags

-- | The flags an 'Index' may have.
data IndexFlags = IndexWritable -- ^ the index is writable
                | IndexReadable -- ^ the index is readable
                  deriving (Eq, Bounded, Show)
instance Enum IndexFlags where
    toEnum n | n == 16 = IndexWritable
{-# LINE 217 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 32 = IndexReadable
{-# LINE 218 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum IndexWritable = 16
{-# LINE 219 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum IndexReadable = 32
{-# LINE 220 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
instance Flags IndexFlags

-- | The flags a 'MiniObject' may have.
data MiniObjectFlags = MiniObjectReadOnly -- ^ the object is not writable
                       deriving (Eq, Bounded, Show)
instance Enum MiniObjectFlags where
    toEnum n | n == 1 = MiniObjectReadOnly
{-# LINE 227 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MiniObjectReadOnly = 1
{-# LINE 228 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
instance Flags MiniObjectFlags

-- | The flags a 'Buffer' may have.
data BufferFlags = BufferPreroll   -- ^ the buffer is part of a preroll and should not be displayed
                 | BufferDiscont   -- ^ the buffer marks a discontinuity in the stream
                 | BufferInCaps    -- ^ the buffer has been added as a field in a 'Caps'
                 | BufferGap       -- ^ the buffer has been created to fill a gap in the stream
                 | BufferDeltaUnit -- ^ the buffer cannot be decoded independently
                   deriving (Eq, Bounded, Show)
instance Enum BufferFlags where
    toEnum n | n == 16    = BufferPreroll
{-# LINE 239 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 32    = BufferDiscont
{-# LINE 240 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 64    = BufferInCaps
{-# LINE 241 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 128        = BufferGap
{-# LINE 242 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 256 = BufferDeltaUnit
{-# LINE 243 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum BufferPreroll   = 16
{-# LINE 244 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum BufferDiscont   = 32
{-# LINE 245 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum BufferInCaps    = 64
{-# LINE 246 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum BufferGap       = 128
{-# LINE 247 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum BufferDeltaUnit = 256
{-# LINE 248 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
instance Flags BufferFlags

-- | The event types that may occur in a pipeline.
data EventType = EventUnknown             -- ^ an unknown event
               | EventFlushStart          -- ^ start a flush operation
               | EventFlushStop           -- ^ stop a flush operation
               | EventEOS                 -- ^ end of stream
               | EventNewSegment          -- ^ a new segment follows in the dataflow
               | EventTag                 -- ^ a new set of metadata tags has been found
               | EventBufferSize          -- ^ notification of buffering requirements
               | EventQOS                 -- ^ quality of service notification
               | EventSeek                -- ^ a request for a new playback position and rate
               | EventNavigation          -- ^ notification of user request

{-# LINE 262 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
               | EventLatency             -- ^ notification of latency adjustment

{-# LINE 264 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
               | EventCustomUpstream      -- ^ custom upstream event
               | EventCustomDownstream    -- ^ custom downstream event
               | EventCustomDownstreamOOB -- ^ custom downstream out-of-band event
               | EventCustomBoth          -- ^ custom bidirectional event
               | EventCustomBothOOB       -- ^ custom bidirectional out-of-band event
                 deriving (Eq, Bounded, Show)
instance Enum EventType where
    toEnum n | n == 0 = EventUnknown
{-# LINE 272 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 19 = EventFlushStart
{-# LINE 273 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 39 = EventFlushStop
{-# LINE 274 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 86 = EventEOS
{-# LINE 275 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 102 = EventNewSegment
{-# LINE 276 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 118 = EventTag
{-# LINE 277 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 134 = EventBufferSize
{-# LINE 278 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 241 = EventQOS
{-# LINE 279 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 257 = EventSeek
{-# LINE 280 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 273 = EventNavigation
{-# LINE 281 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 282 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 289 = EventLatency
{-# LINE 283 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 284 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 513 = EventCustomUpstream
{-# LINE 285 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 518 = EventCustomDownstream
{-# LINE 286 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 514 = EventCustomDownstreamOOB
{-# LINE 287 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 519 = EventCustomBoth
{-# LINE 288 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 515 = EventCustomBothOOB
{-# LINE 289 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

    fromEnum EventUnknown             = 0
{-# LINE 291 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventFlushStart          = 19
{-# LINE 292 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventFlushStop           = 39
{-# LINE 293 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventEOS                 = 86
{-# LINE 294 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventNewSegment          = 102
{-# LINE 295 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventTag                 = 118
{-# LINE 296 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventBufferSize          = 134
{-# LINE 297 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventQOS                 = 241
{-# LINE 298 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventSeek                = 257
{-# LINE 299 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventNavigation          = 273
{-# LINE 300 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 301 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventLatency             = 289
{-# LINE 302 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 303 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventCustomUpstream      = 513
{-# LINE 304 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventCustomDownstream    = 518
{-# LINE 305 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventCustomDownstreamOOB = 514
{-# LINE 306 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventCustomBoth          = 519
{-# LINE 307 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum EventCustomBothOOB       = 515
{-# LINE 308 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

-- | The messages types that may be sent by a pipeline.
data MessageType = MessageEOS             -- ^ end-of-stream
                 | MessageError           -- ^ an error message
                 | MessageWarning         -- ^ a warning message
                 | MessageInfo            -- ^ an informational message
                 | MessageTag             -- ^ a metadata tag
                 | MessageBuffering       -- ^ the pipeline is buffering
                 | MessageStateChanged    -- ^ the pipeline changed state
                 | MessageStepDone        -- ^ a framestep finished
                 | MessageClockProvide    -- ^ an element is able to provide a clock
                 | MessageClockLost       -- ^ the current clock has become unusable
                 | MessageNewClock        -- ^ a new clock was selected by the pipeline
                 | MessageStructureChange -- ^ the structure of the pipeline has changed
                 | MessageStreamStatus    -- ^ a stream status message
                 | MessageApplication     -- ^ a message posted by the application
                 | MessageElement         -- ^ an element specific message
                 | MessageSegmentStart    -- ^ the pipeline started playback of a segment
                 | MessageSegmentDone     -- ^ the pipeline finished playback of a segment
                 | MessageDuration        -- ^ the duration of the pipeline changed

{-# LINE 329 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
                 | MessageLatency         -- ^ an element's latency has changed

{-# LINE 331 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 332 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
                 | MessageAsyncStart      -- ^ an element has started an async state change; used internally
                 | MessageAsyncDone       -- ^ an element has completed an async state change; used internally

{-# LINE 335 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
                   deriving (Eq, Bounded, Show)
instance Enum MessageType where
    toEnum n | n == 1               = MessageEOS
{-# LINE 338 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 2             = MessageError
{-# LINE 339 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 4           = MessageWarning
{-# LINE 340 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 8              = MessageInfo
{-# LINE 341 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 16               = MessageTag
{-# LINE 342 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 32         = MessageBuffering
{-# LINE 343 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 64     = MessageStateChanged
{-# LINE 344 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 256         = MessageStepDone
{-# LINE 345 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 512     = MessageClockProvide
{-# LINE 346 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 1024        = MessageClockLost
{-# LINE 347 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 2048         = MessageNewClock
{-# LINE 348 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 4096  = MessageStructureChange
{-# LINE 349 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 8192     = MessageStreamStatus
{-# LINE 350 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 16384       = MessageApplication
{-# LINE 351 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 32768           = MessageElement
{-# LINE 352 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 65536     = MessageSegmentStart
{-# LINE 353 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 131072      = MessageSegmentDone
{-# LINE 354 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 262144          = MessageDuration
{-# LINE 355 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 356 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 524288           = MessageLatency
{-# LINE 357 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 358 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 359 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 1048576       = MessageAsyncStart
{-# LINE 360 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
             | n == 2097152        = MessageAsyncDone
{-# LINE 361 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 362 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageEOS             = 1
{-# LINE 363 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageError           = 2
{-# LINE 364 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageWarning         = 4
{-# LINE 365 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageInfo            = 8
{-# LINE 366 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageTag             = 16
{-# LINE 367 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageBuffering       = 32
{-# LINE 368 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageStateChanged    = 64
{-# LINE 369 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageStepDone        = 256
{-# LINE 370 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageClockProvide    = 512
{-# LINE 371 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageClockLost       = 1024
{-# LINE 372 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageNewClock        = 2048
{-# LINE 373 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageStructureChange = 4096
{-# LINE 374 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageStreamStatus    = 8192
{-# LINE 375 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageApplication     = 16384
{-# LINE 376 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageElement         = 32768
{-# LINE 377 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageSegmentStart    = 65536
{-# LINE 378 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageSegmentDone     = 131072
{-# LINE 379 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageDuration        = 262144
{-# LINE 380 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 381 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageLatency         = 524288
{-# LINE 382 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 383 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 384 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageAsyncStart      = 1048576
{-# LINE 385 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum MessageAsyncDone       = 2097152
{-# LINE 386 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}

{-# LINE 387 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
instance Flags MessageType

-- | The flags that a 'Caps' may have.
data CapsFlags = CapsAny
                 deriving (Eq, Bounded, Show)
instance Enum CapsFlags where
    toEnum n | n == 1 = CapsAny
{-# LINE 394 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
    fromEnum CapsAny = 1
{-# LINE 395 "Media/Streaming/GStreamer/Core/Constants.hsc" #-}
instance Flags CapsFlags