{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (inaki@blueleaf.cc)
-}

#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
       && !defined(__HADDOCK_VERSION__))

module GI.Gst.Enums
    (

 -- * Enumerations
-- ** BufferingMode #enum:BufferingMode#

    BufferingMode(..)                       ,


-- ** BusSyncReply #enum:BusSyncReply#

    BusSyncReply(..)                        ,


-- ** CapsIntersectMode #enum:CapsIntersectMode#

    CapsIntersectMode(..)                   ,


-- ** ClockEntryType #enum:ClockEntryType#

    ClockEntryType(..)                      ,


-- ** ClockReturn #enum:ClockReturn#

    ClockReturn(..)                         ,


-- ** ClockType #enum:ClockType#

    ClockType(..)                           ,


-- ** CoreError #enum:CoreError#

    CoreError(..)                           ,
    catchCoreError                          ,
    handleCoreError                         ,


-- ** DebugColorMode #enum:DebugColorMode#

    DebugColorMode(..)                      ,


-- ** DebugLevel #enum:DebugLevel#

    DebugLevel(..)                          ,


-- ** EventType #enum:EventType#

    EventType(..)                           ,


-- ** FlowReturn #enum:FlowReturn#

    FlowReturn(..)                          ,


-- ** Format #enum:Format#

    Format(..)                              ,


-- ** IteratorItem #enum:IteratorItem#

    IteratorItem(..)                        ,


-- ** IteratorResult #enum:IteratorResult#

    IteratorResult(..)                      ,


-- ** LibraryError #enum:LibraryError#

    LibraryError(..)                        ,
    catchLibraryError                       ,
    handleLibraryError                      ,


-- ** PadDirection #enum:PadDirection#

    PadDirection(..)                        ,


-- ** PadLinkReturn #enum:PadLinkReturn#

    PadLinkReturn(..)                       ,


-- ** PadMode #enum:PadMode#

    PadMode(..)                             ,


-- ** PadPresence #enum:PadPresence#

    PadPresence(..)                         ,


-- ** PadProbeReturn #enum:PadProbeReturn#

    PadProbeReturn(..)                      ,


-- ** ParseError #enum:ParseError#

    ParseError(..)                          ,
    catchParseError                         ,
    handleParseError                        ,


-- ** PluginError #enum:PluginError#

    PluginError(..)                         ,
    catchPluginError                        ,
    handlePluginError                       ,


-- ** ProgressType #enum:ProgressType#

    ProgressType(..)                        ,


-- ** PromiseResult #enum:PromiseResult#

    PromiseResult(..)                       ,


-- ** QOSType #enum:QOSType#

    QOSType(..)                             ,


-- ** QueryType #enum:QueryType#

    QueryType(..)                           ,


-- ** Rank #enum:Rank#

    Rank(..)                                ,


-- ** ResourceError #enum:ResourceError#

    ResourceError(..)                       ,
    catchResourceError                      ,
    handleResourceError                     ,


-- ** SearchMode #enum:SearchMode#

    SearchMode(..)                          ,


-- ** SeekType #enum:SeekType#

    SeekType(..)                            ,


-- ** State #enum:State#

    State(..)                               ,


-- ** StateChange #enum:StateChange#

    StateChange(..)                         ,


-- ** StateChangeReturn #enum:StateChangeReturn#

    StateChangeReturn(..)                   ,


-- ** StreamError #enum:StreamError#

    StreamError(..)                         ,
    catchStreamError                        ,
    handleStreamError                       ,


-- ** StreamStatusType #enum:StreamStatusType#

    StreamStatusType(..)                    ,


-- ** StructureChangeType #enum:StructureChangeType#

    StructureChangeType(..)                 ,


-- ** TagFlag #enum:TagFlag#

    TagFlag(..)                             ,


-- ** TagMergeMode #enum:TagMergeMode#

    TagMergeMode(..)                        ,


-- ** TagScope #enum:TagScope#

    TagScope(..)                            ,


-- ** TaskState #enum:TaskState#

    TaskState(..)                           ,


-- ** TocEntryType #enum:TocEntryType#

    TocEntryType(..)                        ,


-- ** TocLoopType #enum:TocLoopType#

    TocLoopType(..)                         ,


-- ** TocScope #enum:TocScope#

    TocScope(..)                            ,


-- ** TracerValueScope #enum:TracerValueScope#

    TracerValueScope(..)                    ,


-- ** TypeFindProbability #enum:TypeFindProbability#

    TypeFindProbability(..)                 ,


-- ** URIError #enum:URIError#

    URIError(..)                            ,
    catchURIError                           ,
    handleURIError                          ,


-- ** URIType #enum:URIType#

    URIType(..)                             ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL


-- Enum URIType
{- |
The different types of URI direction.
-}
data URIType =
      URITypeUnknown
    {- ^
    The URI direction is unknown
    -}
    | URITypeSink
    {- ^
    The URI is a consumer.
    -}
    | URITypeSrc
    {- ^
    The URI is a producer.
    -}
    | AnotherURIType Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum URIType where
    fromEnum URITypeUnknown = 0
    fromEnum URITypeSink = 1
    fromEnum URITypeSrc = 2
    fromEnum (AnotherURIType k) = k

    toEnum 0 = URITypeUnknown
    toEnum 1 = URITypeSink
    toEnum 2 = URITypeSrc
    toEnum k = AnotherURIType k

instance P.Ord URIType where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_uri_type_get_type" c_gst_uri_type_get_type ::
    IO GType

instance BoxedEnum URIType where
    boxedEnumType _ = c_gst_uri_type_get_type

-- Enum URIError
{- |
Different URI-related errors that can occur.
-}
data URIError =
      URIErrorUnsupportedProtocol
    {- ^
    The protocol is not supported
    -}
    | URIErrorBadUri
    {- ^
    There was a problem with the URI
    -}
    | URIErrorBadState
    {- ^
    Could not set or change the URI because the
        URI handler was in a state where that is not possible or not permitted
    -}
    | URIErrorBadReference
    {- ^
    There was a problem with the entity that
        the URI references
    -}
    | AnotherURIError Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum URIError where
    fromEnum URIErrorUnsupportedProtocol = 0
    fromEnum URIErrorBadUri = 1
    fromEnum URIErrorBadState = 2
    fromEnum URIErrorBadReference = 3
    fromEnum (AnotherURIError k) = k

    toEnum 0 = URIErrorUnsupportedProtocol
    toEnum 1 = URIErrorBadUri
    toEnum 2 = URIErrorBadState
    toEnum 3 = URIErrorBadReference
    toEnum k = AnotherURIError k

instance P.Ord URIError where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

instance GErrorClass URIError where
    gerrorClassDomain _ = "gst-uri-error-quark"

-- | Catch exceptions of type `URIError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchURIError ::
    IO a ->
    (URIError -> GErrorMessage -> IO a) ->
    IO a
catchURIError = catchGErrorJustDomain

-- | Handle exceptions of type `URIError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleURIError ::
    (URIError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleURIError = handleGErrorJustDomain

foreign import ccall "gst_uri_error_get_type" c_gst_uri_error_get_type ::
    IO GType

instance BoxedEnum URIError where
    boxedEnumType _ = c_gst_uri_error_get_type

-- Enum TypeFindProbability
{- |
The probability of the typefind function. Higher values have more certainty
in doing a reliable typefind.
-}
data TypeFindProbability =
      TypeFindProbabilityNone
    {- ^
    type undetected.
    -}
    | TypeFindProbabilityMinimum
    {- ^
    unlikely typefind.
    -}
    | TypeFindProbabilityPossible
    {- ^
    possible type detected.
    -}
    | TypeFindProbabilityLikely
    {- ^
    likely a type was detected.
    -}
    | TypeFindProbabilityNearlyCertain
    {- ^
    nearly certain that a type was detected.
    -}
    | TypeFindProbabilityMaximum
    {- ^
    very certain a type was detected.
    -}
    | AnotherTypeFindProbability Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum TypeFindProbability where
    fromEnum TypeFindProbabilityNone = 0
    fromEnum TypeFindProbabilityMinimum = 1
    fromEnum TypeFindProbabilityPossible = 50
    fromEnum TypeFindProbabilityLikely = 80
    fromEnum TypeFindProbabilityNearlyCertain = 99
    fromEnum TypeFindProbabilityMaximum = 100
    fromEnum (AnotherTypeFindProbability k) = k

    toEnum 0 = TypeFindProbabilityNone
    toEnum 1 = TypeFindProbabilityMinimum
    toEnum 50 = TypeFindProbabilityPossible
    toEnum 80 = TypeFindProbabilityLikely
    toEnum 99 = TypeFindProbabilityNearlyCertain
    toEnum 100 = TypeFindProbabilityMaximum
    toEnum k = AnotherTypeFindProbability k

instance P.Ord TypeFindProbability where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_type_find_probability_get_type" c_gst_type_find_probability_get_type ::
    IO GType

instance BoxedEnum TypeFindProbability where
    boxedEnumType _ = c_gst_type_find_probability_get_type

-- Enum TracerValueScope
{- |
Tracing record will contain fields that contain a measured value or extra
meta-data. One such meta data are values that tell where a measurement was
taken. This enumerating declares to which scope such a meta data field
relates to. If it is e.g. 'GI.Gst.Enums.TracerValueScopePad', then each of the log
events may contain values for different @/GstPads/@.

/Since: 1.8/
-}
data TracerValueScope =
      TracerValueScopeProcess
    {- ^
    the value is related to the process
    -}
    | TracerValueScopeThread
    {- ^
    the value is related to a thread
    -}
    | TracerValueScopeElement
    {- ^
    the value is related to an 'GI.Gst.Objects.Element.Element'
    -}
    | TracerValueScopePad
    {- ^
    the value is related to a 'GI.Gst.Objects.Pad.Pad'
    -}
    | AnotherTracerValueScope Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum TracerValueScope where
    fromEnum TracerValueScopeProcess = 0
    fromEnum TracerValueScopeThread = 1
    fromEnum TracerValueScopeElement = 2
    fromEnum TracerValueScopePad = 3
    fromEnum (AnotherTracerValueScope k) = k

    toEnum 0 = TracerValueScopeProcess
    toEnum 1 = TracerValueScopeThread
    toEnum 2 = TracerValueScopeElement
    toEnum 3 = TracerValueScopePad
    toEnum k = AnotherTracerValueScope k

instance P.Ord TracerValueScope where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_tracer_value_scope_get_type" c_gst_tracer_value_scope_get_type ::
    IO GType

instance BoxedEnum TracerValueScope where
    boxedEnumType _ = c_gst_tracer_value_scope_get_type

-- Enum TocScope
{- |
The scope of a TOC.
-}
data TocScope =
      TocScopeGlobal
    {- ^
    global TOC representing all selectable options
        (this is what applications are usually interested in)
    -}
    | TocScopeCurrent
    {- ^
    TOC for the currently active\/selected stream
        (this is a TOC representing the current stream from start to EOS,
        and is what a TOC writer \/ muxer is usually interested in; it will
        usually be a subset of the global TOC, e.g. just the chapters of
        the current title, or the chapters selected for playback from the
        current title)
    -}
    | AnotherTocScope Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum TocScope where
    fromEnum TocScopeGlobal = 1
    fromEnum TocScopeCurrent = 2
    fromEnum (AnotherTocScope k) = k

    toEnum 1 = TocScopeGlobal
    toEnum 2 = TocScopeCurrent
    toEnum k = AnotherTocScope k

instance P.Ord TocScope where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_toc_scope_get_type" c_gst_toc_scope_get_type ::
    IO GType

instance BoxedEnum TocScope where
    boxedEnumType _ = c_gst_toc_scope_get_type

-- Enum TocLoopType
{- |
How a 'GI.Gst.Structs.TocEntry.TocEntry' should be repeated. By default, entries are played a
single time.

/Since: 1.4/
-}
data TocLoopType =
      TocLoopTypeNone
    {- ^
    single forward playback
    -}
    | TocLoopTypeForward
    {- ^
    repeat forward
    -}
    | TocLoopTypeReverse
    {- ^
    repeat backward
    -}
    | TocLoopTypePingPong
    {- ^
    repeat forward and backward
    -}
    | AnotherTocLoopType Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum TocLoopType where
    fromEnum TocLoopTypeNone = 0
    fromEnum TocLoopTypeForward = 1
    fromEnum TocLoopTypeReverse = 2
    fromEnum TocLoopTypePingPong = 3
    fromEnum (AnotherTocLoopType k) = k

    toEnum 0 = TocLoopTypeNone
    toEnum 1 = TocLoopTypeForward
    toEnum 2 = TocLoopTypeReverse
    toEnum 3 = TocLoopTypePingPong
    toEnum k = AnotherTocLoopType k

instance P.Ord TocLoopType where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_toc_loop_type_get_type" c_gst_toc_loop_type_get_type ::
    IO GType

instance BoxedEnum TocLoopType where
    boxedEnumType _ = c_gst_toc_loop_type_get_type

-- Enum TocEntryType
{- |
The different types of TOC entries (see 'GI.Gst.Structs.TocEntry.TocEntry').

There are two types of TOC entries: alternatives or parts in a sequence.
-}
data TocEntryType =
      TocEntryTypeAngle
    {- ^
    entry is an angle (i.e. an alternative)
    -}
    | TocEntryTypeVersion
    {- ^
    entry is a version (i.e. alternative)
    -}
    | TocEntryTypeEdition
    {- ^
    entry is an edition (i.e. alternative)
    -}
    | TocEntryTypeInvalid
    {- ^
    invalid entry type value
    -}
    | TocEntryTypeTitle
    {- ^
    entry is a title (i.e. a part of a sequence)
    -}
    | TocEntryTypeTrack
    {- ^
    entry is a track (i.e. a part of a sequence)
    -}
    | TocEntryTypeChapter
    {- ^
    entry is a chapter (i.e. a part of a sequence)
    -}
    | AnotherTocEntryType Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum TocEntryType where
    fromEnum TocEntryTypeAngle = -3
    fromEnum TocEntryTypeVersion = -2
    fromEnum TocEntryTypeEdition = -1
    fromEnum TocEntryTypeInvalid = 0
    fromEnum TocEntryTypeTitle = 1
    fromEnum TocEntryTypeTrack = 2
    fromEnum TocEntryTypeChapter = 3
    fromEnum (AnotherTocEntryType k) = k

    toEnum -3 = TocEntryTypeAngle
    toEnum -2 = TocEntryTypeVersion
    toEnum -1 = TocEntryTypeEdition
    toEnum 0 = TocEntryTypeInvalid
    toEnum 1 = TocEntryTypeTitle
    toEnum 2 = TocEntryTypeTrack
    toEnum 3 = TocEntryTypeChapter
    toEnum k = AnotherTocEntryType k

instance P.Ord TocEntryType where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_toc_entry_type_get_type" c_gst_toc_entry_type_get_type ::
    IO GType

instance BoxedEnum TocEntryType where
    boxedEnumType _ = c_gst_toc_entry_type_get_type

-- Enum TaskState
{- |
The different states a task can be in
-}
data TaskState =
      TaskStateStarted
    {- ^
    the task is started and running
    -}
    | TaskStateStopped
    {- ^
    the task is stopped
    -}
    | TaskStatePaused
    {- ^
    the task is paused
    -}
    | AnotherTaskState Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum TaskState where
    fromEnum TaskStateStarted = 0
    fromEnum TaskStateStopped = 1
    fromEnum TaskStatePaused = 2
    fromEnum (AnotherTaskState k) = k

    toEnum 0 = TaskStateStarted
    toEnum 1 = TaskStateStopped
    toEnum 2 = TaskStatePaused
    toEnum k = AnotherTaskState k

instance P.Ord TaskState where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_task_state_get_type" c_gst_task_state_get_type ::
    IO GType

instance BoxedEnum TaskState where
    boxedEnumType _ = c_gst_task_state_get_type

-- Enum TagScope
{- |
GstTagScope specifies if a taglist applies to the complete
medium or only to one single stream.
-}
data TagScope =
      TagScopeStream
    {- ^
    tags specific to this single stream
    -}
    | TagScopeGlobal
    {- ^
    global tags for the complete medium
    -}
    | AnotherTagScope Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum TagScope where
    fromEnum TagScopeStream = 0
    fromEnum TagScopeGlobal = 1
    fromEnum (AnotherTagScope k) = k

    toEnum 0 = TagScopeStream
    toEnum 1 = TagScopeGlobal
    toEnum k = AnotherTagScope k

instance P.Ord TagScope where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_tag_scope_get_type" c_gst_tag_scope_get_type ::
    IO GType

instance BoxedEnum TagScope where
    boxedEnumType _ = c_gst_tag_scope_get_type

-- Enum TagMergeMode
{- |
The different tag merging modes are basically replace, overwrite and append,
but they can be seen from two directions. Given two taglists: (A) the tags
already in the element and (B) the ones that are supplied to the element (
e.g. via 'GI.Gst.Interfaces.TagSetter.tagSetterMergeTags' \/ @/gst_tag_setter_add_tags()/@ or a
'GI.Gst.Enums.EventTypeTag'), how are these tags merged?
In the table below this is shown for the cases that a tag exists in the list
(A) or does not exists (!A) and combinations thereof.

\<table frame=\"all\" colsep=\"1\" rowsep=\"1\">
  \<title>merge mode\<\/title>
  \<tgroup cols=\'5\' align=\'left\'>
    \<thead>
      \<row>
        \<entry>merge mode\<\/entry>
        \<entry>A + B\<\/entry>
        \<entry>A + !B\<\/entry>
        \<entry>!A + B\<\/entry>
        \<entry>!A + !B\<\/entry>
      \<\/row>
    \<\/thead>
    \<tbody>
      \<row>
        \<entry>REPLACE_ALL\<\/entry>
        \<entry>B\<\/entry>
        \<entry>-\<\/entry>
        \<entry>B\<\/entry>
        \<entry>-\<\/entry>
      \<\/row>
      \<row>
        \<entry>REPLACE\<\/entry>
        \<entry>B\<\/entry>
        \<entry>A\<\/entry>
        \<entry>B\<\/entry>
        \<entry>-\<\/entry>
      \<\/row>
      \<row>
        \<entry>APPEND\<\/entry>
        \<entry>A, B\<\/entry>
        \<entry>A\<\/entry>
        \<entry>B\<\/entry>
        \<entry>-\<\/entry>
      \<\/row>
      \<row>
        \<entry>PREPEND\<\/entry>
        \<entry>B, A\<\/entry>
        \<entry>A\<\/entry>
        \<entry>B\<\/entry>
        \<entry>-\<\/entry>
      \<\/row>
      \<row>
        \<entry>KEEP\<\/entry>
        \<entry>A\<\/entry>
        \<entry>A\<\/entry>
        \<entry>B\<\/entry>
        \<entry>-\<\/entry>
      \<\/row>
      \<row>
        \<entry>KEEP_ALL\<\/entry>
        \<entry>A\<\/entry>
        \<entry>A\<\/entry>
        \<entry>-\<\/entry>
        \<entry>-\<\/entry>
      \<\/row>
    \<\/tbody>
  \<\/tgroup>
\<\/table>
-}
data TagMergeMode =
      TagMergeModeUndefined
    {- ^
    undefined merge mode
    -}
    | TagMergeModeReplaceAll
    {- ^
    replace all tags (clear list and append)
    -}
    | TagMergeModeReplace
    {- ^
    replace tags
    -}
    | TagMergeModeAppend
    {- ^
    append tags
    -}
    | TagMergeModePrepend
    {- ^
    prepend tags
    -}
    | TagMergeModeKeep
    {- ^
    keep existing tags
    -}
    | TagMergeModeKeepAll
    {- ^
    keep all existing tags
    -}
    | TagMergeModeCount
    {- ^
    the number of merge modes
    -}
    | AnotherTagMergeMode Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum TagMergeMode where
    fromEnum TagMergeModeUndefined = 0
    fromEnum TagMergeModeReplaceAll = 1
    fromEnum TagMergeModeReplace = 2
    fromEnum TagMergeModeAppend = 3
    fromEnum TagMergeModePrepend = 4
    fromEnum TagMergeModeKeep = 5
    fromEnum TagMergeModeKeepAll = 6
    fromEnum TagMergeModeCount = 7
    fromEnum (AnotherTagMergeMode k) = k

    toEnum 0 = TagMergeModeUndefined
    toEnum 1 = TagMergeModeReplaceAll
    toEnum 2 = TagMergeModeReplace
    toEnum 3 = TagMergeModeAppend
    toEnum 4 = TagMergeModePrepend
    toEnum 5 = TagMergeModeKeep
    toEnum 6 = TagMergeModeKeepAll
    toEnum 7 = TagMergeModeCount
    toEnum k = AnotherTagMergeMode k

instance P.Ord TagMergeMode where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_tag_merge_mode_get_type" c_gst_tag_merge_mode_get_type ::
    IO GType

instance BoxedEnum TagMergeMode where
    boxedEnumType _ = c_gst_tag_merge_mode_get_type

-- Enum TagFlag
{- |
Extra tag flags used when registering tags.
-}
data TagFlag =
      TagFlagUndefined
    {- ^
    undefined flag
    -}
    | TagFlagMeta
    {- ^
    tag is meta data
    -}
    | TagFlagEncoded
    {- ^
    tag is encoded
    -}
    | TagFlagDecoded
    {- ^
    tag is decoded
    -}
    | TagFlagCount
    {- ^
    number of tag flags
    -}
    | AnotherTagFlag Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum TagFlag where
    fromEnum TagFlagUndefined = 0
    fromEnum TagFlagMeta = 1
    fromEnum TagFlagEncoded = 2
    fromEnum TagFlagDecoded = 3
    fromEnum TagFlagCount = 4
    fromEnum (AnotherTagFlag k) = k

    toEnum 0 = TagFlagUndefined
    toEnum 1 = TagFlagMeta
    toEnum 2 = TagFlagEncoded
    toEnum 3 = TagFlagDecoded
    toEnum 4 = TagFlagCount
    toEnum k = AnotherTagFlag k

instance P.Ord TagFlag where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_tag_flag_get_type" c_gst_tag_flag_get_type ::
    IO GType

instance BoxedEnum TagFlag where
    boxedEnumType _ = c_gst_tag_flag_get_type

-- Enum StructureChangeType
{- |
The type of a 'GI.Gst.Flags.MessageTypeStructureChange'.
-}
data StructureChangeType =
      StructureChangeTypeLink
    {- ^
    Pad linking is starting or done.
    -}
    | StructureChangeTypeUnlink
    {- ^
    Pad unlinking is starting or done.
    -}
    | AnotherStructureChangeType Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum StructureChangeType where
    fromEnum StructureChangeTypeLink = 0
    fromEnum StructureChangeTypeUnlink = 1
    fromEnum (AnotherStructureChangeType k) = k

    toEnum 0 = StructureChangeTypeLink
    toEnum 1 = StructureChangeTypeUnlink
    toEnum k = AnotherStructureChangeType k

instance P.Ord StructureChangeType where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_structure_change_type_get_type" c_gst_structure_change_type_get_type ::
    IO GType

instance BoxedEnum StructureChangeType where
    boxedEnumType _ = c_gst_structure_change_type_get_type

-- Enum StreamStatusType
{- |
The type of a 'GI.Gst.Flags.MessageTypeStreamStatus'. The stream status messages inform the
application of new streaming threads and their status.
-}
data StreamStatusType =
      StreamStatusTypeCreate
    {- ^
    A new thread need to be created.
    -}
    | StreamStatusTypeEnter
    {- ^
    a thread entered its loop function
    -}
    | StreamStatusTypeLeave
    {- ^
    a thread left its loop function
    -}
    | StreamStatusTypeDestroy
    {- ^
    a thread is destroyed
    -}
    | StreamStatusTypeStart
    {- ^
    a thread is started
    -}
    | StreamStatusTypePause
    {- ^
    a thread is paused
    -}
    | StreamStatusTypeStop
    {- ^
    a thread is stopped
    -}
    | AnotherStreamStatusType Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum StreamStatusType where
    fromEnum StreamStatusTypeCreate = 0
    fromEnum StreamStatusTypeEnter = 1
    fromEnum StreamStatusTypeLeave = 2
    fromEnum StreamStatusTypeDestroy = 3
    fromEnum StreamStatusTypeStart = 8
    fromEnum StreamStatusTypePause = 9
    fromEnum StreamStatusTypeStop = 10
    fromEnum (AnotherStreamStatusType k) = k

    toEnum 0 = StreamStatusTypeCreate
    toEnum 1 = StreamStatusTypeEnter
    toEnum 2 = StreamStatusTypeLeave
    toEnum 3 = StreamStatusTypeDestroy
    toEnum 8 = StreamStatusTypeStart
    toEnum 9 = StreamStatusTypePause
    toEnum 10 = StreamStatusTypeStop
    toEnum k = AnotherStreamStatusType k

instance P.Ord StreamStatusType where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_stream_status_type_get_type" c_gst_stream_status_type_get_type ::
    IO GType

instance BoxedEnum StreamStatusType where
    boxedEnumType _ = c_gst_stream_status_type_get_type

-- Enum StreamError
{- |
Stream errors are for anything related to the stream being processed:
format errors, media type errors, ...
They\'re typically used by decoders, demuxers, converters, ...
-}
data StreamError =
      StreamErrorFailed
    {- ^
    a general error which doesn\'t fit in any other
    category.  Make sure you add a custom message to the error call.
    -}
    | StreamErrorTooLazy
    {- ^
    do not use this except as a placeholder for
    deciding where to go while developing code.
    -}
    | StreamErrorNotImplemented
    {- ^
    use this when you do not want to implement
    this functionality yet.
    -}
    | StreamErrorTypeNotFound
    {- ^
    used when the element doesn\'t know the
    stream\'s type.
    -}
    | StreamErrorWrongType
    {- ^
    used when the element doesn\'t handle this type
    of stream.
    -}
    | StreamErrorCodecNotFound
    {- ^
    used when there\'s no codec to handle the
    stream\'s type.
    -}
    | StreamErrorDecode
    {- ^
    used when decoding fails.
    -}
    | StreamErrorEncode
    {- ^
    used when encoding fails.
    -}
    | StreamErrorDemux
    {- ^
    used when demuxing fails.
    -}
    | StreamErrorMux
    {- ^
    used when muxing fails.
    -}
    | StreamErrorFormat
    {- ^
    used when the stream is of the wrong format
    (for example, wrong caps).
    -}
    | StreamErrorDecrypt
    {- ^
    used when the stream is encrypted and can\'t be
    decrypted because this is not supported by the element.
    -}
    | StreamErrorDecryptNokey
    {- ^
    used when the stream is encrypted and
    can\'t be decrypted because no suitable key is available.
    -}
    | StreamErrorNumErrors
    {- ^
    the number of stream error types.
    -}
    | AnotherStreamError Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum StreamError where
    fromEnum StreamErrorFailed = 1
    fromEnum StreamErrorTooLazy = 2
    fromEnum StreamErrorNotImplemented = 3
    fromEnum StreamErrorTypeNotFound = 4
    fromEnum StreamErrorWrongType = 5
    fromEnum StreamErrorCodecNotFound = 6
    fromEnum StreamErrorDecode = 7
    fromEnum StreamErrorEncode = 8
    fromEnum StreamErrorDemux = 9
    fromEnum StreamErrorMux = 10
    fromEnum StreamErrorFormat = 11
    fromEnum StreamErrorDecrypt = 12
    fromEnum StreamErrorDecryptNokey = 13
    fromEnum StreamErrorNumErrors = 14
    fromEnum (AnotherStreamError k) = k

    toEnum 1 = StreamErrorFailed
    toEnum 2 = StreamErrorTooLazy
    toEnum 3 = StreamErrorNotImplemented
    toEnum 4 = StreamErrorTypeNotFound
    toEnum 5 = StreamErrorWrongType
    toEnum 6 = StreamErrorCodecNotFound
    toEnum 7 = StreamErrorDecode
    toEnum 8 = StreamErrorEncode
    toEnum 9 = StreamErrorDemux
    toEnum 10 = StreamErrorMux
    toEnum 11 = StreamErrorFormat
    toEnum 12 = StreamErrorDecrypt
    toEnum 13 = StreamErrorDecryptNokey
    toEnum 14 = StreamErrorNumErrors
    toEnum k = AnotherStreamError k

instance P.Ord StreamError where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

instance GErrorClass StreamError where
    gerrorClassDomain _ = "gst-stream-error-quark"

-- | Catch exceptions of type `StreamError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchStreamError ::
    IO a ->
    (StreamError -> GErrorMessage -> IO a) ->
    IO a
catchStreamError = catchGErrorJustDomain

-- | Handle exceptions of type `StreamError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleStreamError ::
    (StreamError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleStreamError = handleGErrorJustDomain

foreign import ccall "gst_stream_error_get_type" c_gst_stream_error_get_type ::
    IO GType

instance BoxedEnum StreamError where
    boxedEnumType _ = c_gst_stream_error_get_type

-- Enum StateChangeReturn
{- |
The possible return values from a state change function such as
'GI.Gst.Objects.Element.elementSetState'. Only /@gSTSTATECHANGEFAILURE@/ is a real failure.
-}
data StateChangeReturn =
      StateChangeReturnFailure
    {- ^
    the state change failed
    -}
    | StateChangeReturnSuccess
    {- ^
    the state change succeeded
    -}
    | StateChangeReturnAsync
    {- ^
    the state change will happen asynchronously
    -}
    | StateChangeReturnNoPreroll
    {- ^
    the state change succeeded but the element
                                  cannot produce data in 'GI.Gst.Enums.StatePaused'.
                                  This typically happens with live sources.
    -}
    | AnotherStateChangeReturn Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum StateChangeReturn where
    fromEnum StateChangeReturnFailure = 0
    fromEnum StateChangeReturnSuccess = 1
    fromEnum StateChangeReturnAsync = 2
    fromEnum StateChangeReturnNoPreroll = 3
    fromEnum (AnotherStateChangeReturn k) = k

    toEnum 0 = StateChangeReturnFailure
    toEnum 1 = StateChangeReturnSuccess
    toEnum 2 = StateChangeReturnAsync
    toEnum 3 = StateChangeReturnNoPreroll
    toEnum k = AnotherStateChangeReturn k

instance P.Ord StateChangeReturn where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_state_change_return_get_type" c_gst_state_change_return_get_type ::
    IO GType

instance BoxedEnum StateChangeReturn where
    boxedEnumType _ = c_gst_state_change_return_get_type

-- Enum StateChange
{- |
These are the different state changes an element goes through.
'GI.Gst.Enums.StateNull' &rArr; 'GI.Gst.Enums.StatePlaying' is called an upwards state change
and 'GI.Gst.Enums.StatePlaying' &rArr; 'GI.Gst.Enums.StateNull' a downwards state change.
-}
data StateChange =
      StateChangeNullToReady
    {- ^
    state change from NULL to READY.
      * The element must check if the resources it needs are available. Device
        sinks and -sources typically try to probe the device to constrain their
        caps.
      * The element opens the device (in case feature need to be probed).
    -}
    | StateChangeReadyToPaused
    {- ^
    state change from READY to PAUSED.
      * The element pads are activated in order to receive data in PAUSED.
        Streaming threads are started.
      * Some elements might need to return 'GI.Gst.Enums.StateChangeReturnAsync' and complete
        the state change when they have enough information. It is a requirement
        for sinks to return 'GI.Gst.Enums.StateChangeReturnAsync' and complete the state change
        when they receive the first buffer or 'GI.Gst.Enums.EventTypeEos' (preroll).
        Sinks also block the dataflow when in PAUSED.
      * A pipeline resets the running_time to 0.
      * Live sources return 'GI.Gst.Enums.StateChangeReturnNoPreroll' and don\'t generate data.
    -}
    | StateChangePausedToPlaying
    {- ^
    state change from PAUSED to PLAYING.
      * Most elements ignore this state change.
      * The pipeline selects a 'GI.Gst.Objects.Clock.Clock' and distributes this to all the children
        before setting them to PLAYING. This means that it is only allowed to
        synchronize on the 'GI.Gst.Objects.Clock.Clock' in the PLAYING state.
      * The pipeline uses the 'GI.Gst.Objects.Clock.Clock' and the running_time to calculate the
        base_time. The base_time is distributed to all children when performing
        the state change.
      * Sink elements stop blocking on the preroll buffer or event and start
        rendering the data.
      * Sinks can post 'GI.Gst.Flags.MessageTypeEos' in the PLAYING state. It is not allowed
        to post 'GI.Gst.Flags.MessageTypeEos' when not in the PLAYING state.
      * While streaming in PAUSED or PLAYING elements can create and remove
        sometimes pads.
      * Live sources start generating data and return 'GI.Gst.Enums.StateChangeReturnSuccess'.
    -}
    | StateChangePlayingToPaused
    {- ^
    state change from PLAYING to PAUSED.
      * Most elements ignore this state change.
      * The pipeline calculates the running_time based on the last selected
        'GI.Gst.Objects.Clock.Clock' and the base_time. It stores this information to continue
        playback when going back to the PLAYING state.
      * Sinks unblock any 'GI.Gst.Objects.Clock.Clock' wait calls.
      * When a sink does not have a pending buffer to play, it returns
        @/GST_STATE_CHANGE_ASYNC/@ from this state change and completes the state
        change when it receives a new buffer or an 'GI.Gst.Enums.EventTypeEos'.
      * Any queued 'GI.Gst.Flags.MessageTypeEos' items are removed since they will be reposted
        when going back to the PLAYING state. The EOS messages are queued in
        'GI.Gst.Objects.Bin.Bin' containers.
      * Live sources stop generating data and return 'GI.Gst.Enums.StateChangeReturnNoPreroll'.
    -}
    | StateChangePausedToReady
    {- ^
    state change from PAUSED to READY.
      * Sinks unblock any waits in the preroll.
      * Elements unblock any waits on devices
      * Chain or get_range functions return 'GI.Gst.Enums.FlowReturnFlushing'.
      * The element pads are deactivated so that streaming becomes impossible and
        all streaming threads are stopped.
      * The sink forgets all negotiated formats
      * Elements remove all sometimes pads
    -}
    | StateChangeReadyToNull
    {- ^
    state change from READY to NULL.
      * Elements close devices
      * Elements reset any internal state.
    -}
    | StateChangeNullToNull
    {- ^
    state change from NULL to NULL. (Since 1.14)
    -}
    | StateChangeReadyToReady
    {- ^
    state change from READY to READY,
    This might happen when going to PAUSED asynchronously failed, in that case
    elements should make sure they are in a proper, coherent READY state. (Since 1.14)
    -}
    | StateChangePausedToPaused
    {- ^
    state change from PAUSED to PAUSED.
    This might happen when elements were in PLAYING state and \'lost state\',
    they should make sure to go back to real \'PAUSED\' state (prerolling for example). (Since 1.14)
    -}
    | StateChangePlayingToPlaying
    {- ^
    state change from PLAYING to PLAYING. (Since 1.14)
    -}
    | AnotherStateChange Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum StateChange where
    fromEnum StateChangeNullToReady = 10
    fromEnum StateChangeReadyToPaused = 19
    fromEnum StateChangePausedToPlaying = 28
    fromEnum StateChangePlayingToPaused = 35
    fromEnum StateChangePausedToReady = 26
    fromEnum StateChangeReadyToNull = 17
    fromEnum StateChangeNullToNull = 9
    fromEnum StateChangeReadyToReady = 18
    fromEnum StateChangePausedToPaused = 27
    fromEnum StateChangePlayingToPlaying = 36
    fromEnum (AnotherStateChange k) = k

    toEnum 10 = StateChangeNullToReady
    toEnum 19 = StateChangeReadyToPaused
    toEnum 28 = StateChangePausedToPlaying
    toEnum 35 = StateChangePlayingToPaused
    toEnum 26 = StateChangePausedToReady
    toEnum 17 = StateChangeReadyToNull
    toEnum 9 = StateChangeNullToNull
    toEnum 18 = StateChangeReadyToReady
    toEnum 27 = StateChangePausedToPaused
    toEnum 36 = StateChangePlayingToPlaying
    toEnum k = AnotherStateChange k

instance P.Ord StateChange where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_state_change_get_type" c_gst_state_change_get_type ::
    IO GType

instance BoxedEnum StateChange where
    boxedEnumType _ = c_gst_state_change_get_type

-- Enum State
{- |
The possible states an element can be in. States can be changed using
'GI.Gst.Objects.Element.elementSetState' and checked using 'GI.Gst.Objects.Element.elementGetState'.
-}
data State =
      StateVoidPending
    {- ^
    no pending state.
    -}
    | StateNull
    {- ^
    the NULL state or initial state of an element.
    -}
    | StateReady
    {- ^
    the element is ready to go to PAUSED.
    -}
    | StatePaused
    {- ^
    the element is PAUSED, it is ready to accept and
                             process data. Sink elements however only accept one
                             buffer and then block.
    -}
    | StatePlaying
    {- ^
    the element is PLAYING, the 'GI.Gst.Objects.Clock.Clock' is running and
                             the data is flowing.
    -}
    | AnotherState Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum State where
    fromEnum StateVoidPending = 0
    fromEnum StateNull = 1
    fromEnum StateReady = 2
    fromEnum StatePaused = 3
    fromEnum StatePlaying = 4
    fromEnum (AnotherState k) = k

    toEnum 0 = StateVoidPending
    toEnum 1 = StateNull
    toEnum 2 = StateReady
    toEnum 3 = StatePaused
    toEnum 4 = StatePlaying
    toEnum k = AnotherState k

instance P.Ord State where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_state_get_type" c_gst_state_get_type ::
    IO GType

instance BoxedEnum State where
    boxedEnumType _ = c_gst_state_get_type

-- Enum SeekType
{- |
The different types of seek events. When constructing a seek event with
'GI.Gst.Structs.Event.eventNewSeek' or when doing gst_segment_do_seek ().
-}
data SeekType =
      SeekTypeNone
    {- ^
    no change in position is required
    -}
    | SeekTypeSet
    {- ^
    absolute position is requested
    -}
    | SeekTypeEnd
    {- ^
    relative position to duration is requested
    -}
    | AnotherSeekType Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum SeekType where
    fromEnum SeekTypeNone = 0
    fromEnum SeekTypeSet = 1
    fromEnum SeekTypeEnd = 2
    fromEnum (AnotherSeekType k) = k

    toEnum 0 = SeekTypeNone
    toEnum 1 = SeekTypeSet
    toEnum 2 = SeekTypeEnd
    toEnum k = AnotherSeekType k

instance P.Ord SeekType where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_seek_type_get_type" c_gst_seek_type_get_type ::
    IO GType

instance BoxedEnum SeekType where
    boxedEnumType _ = c_gst_seek_type_get_type

-- Enum SearchMode
{- |
The different search modes.
-}
data SearchMode =
      SearchModeExact
    {- ^
    Only search for exact matches.
    -}
    | SearchModeBefore
    {- ^
    Search for an exact match or the element just before.
    -}
    | SearchModeAfter
    {- ^
    Search for an exact match or the element just after.
    -}
    | AnotherSearchMode Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum SearchMode where
    fromEnum SearchModeExact = 0
    fromEnum SearchModeBefore = 1
    fromEnum SearchModeAfter = 2
    fromEnum (AnotherSearchMode k) = k

    toEnum 0 = SearchModeExact
    toEnum 1 = SearchModeBefore
    toEnum 2 = SearchModeAfter
    toEnum k = AnotherSearchMode k

instance P.Ord SearchMode where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_search_mode_get_type" c_gst_search_mode_get_type ::
    IO GType

instance BoxedEnum SearchMode where
    boxedEnumType _ = c_gst_search_mode_get_type

-- Enum ResourceError
{- |
Resource errors are for any resource used by an element:
memory, files, network connections, process space, ...
They\'re typically used by source and sink elements.
-}
data ResourceError =
      ResourceErrorFailed
    {- ^
    a general error which doesn\'t fit in any other
    category.  Make sure you add a custom message to the error call.
    -}
    | ResourceErrorTooLazy
    {- ^
    do not use this except as a placeholder for
    deciding where to go while developing code.
    -}
    | ResourceErrorNotFound
    {- ^
    used when the resource could not be found.
    -}
    | ResourceErrorBusy
    {- ^
    used when resource is busy.
    -}
    | ResourceErrorOpenRead
    {- ^
    used when resource fails to open for reading.
    -}
    | ResourceErrorOpenWrite
    {- ^
    used when resource fails to open for writing.
    -}
    | ResourceErrorOpenReadWrite
    {- ^
    used when resource cannot be opened for
    both reading and writing, or either (but unspecified which).
    -}
    | ResourceErrorClose
    {- ^
    used when the resource can\'t be closed.
    -}
    | ResourceErrorRead
    {- ^
    used when the resource can\'t be read from.
    -}
    | ResourceErrorWrite
    {- ^
    used when the resource can\'t be written to.
    -}
    | ResourceErrorSeek
    {- ^
    used when a seek on the resource fails.
    -}
    | ResourceErrorSync
    {- ^
    used when a synchronize on the resource fails.
    -}
    | ResourceErrorSettings
    {- ^
    used when settings can\'t be manipulated on.
    -}
    | ResourceErrorNoSpaceLeft
    {- ^
    used when the resource has no space left.
    -}
    | ResourceErrorNotAuthorized
    {- ^
    used when the resource can\'t be opened
                                        due to missing authorization.
                                        (Since 1.2.4)
    -}
    | ResourceErrorNumErrors
    {- ^
    the number of resource error types.
    -}
    | AnotherResourceError Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum ResourceError where
    fromEnum ResourceErrorFailed = 1
    fromEnum ResourceErrorTooLazy = 2
    fromEnum ResourceErrorNotFound = 3
    fromEnum ResourceErrorBusy = 4
    fromEnum ResourceErrorOpenRead = 5
    fromEnum ResourceErrorOpenWrite = 6
    fromEnum ResourceErrorOpenReadWrite = 7
    fromEnum ResourceErrorClose = 8
    fromEnum ResourceErrorRead = 9
    fromEnum ResourceErrorWrite = 10
    fromEnum ResourceErrorSeek = 11
    fromEnum ResourceErrorSync = 12
    fromEnum ResourceErrorSettings = 13
    fromEnum ResourceErrorNoSpaceLeft = 14
    fromEnum ResourceErrorNotAuthorized = 15
    fromEnum ResourceErrorNumErrors = 16
    fromEnum (AnotherResourceError k) = k

    toEnum 1 = ResourceErrorFailed
    toEnum 2 = ResourceErrorTooLazy
    toEnum 3 = ResourceErrorNotFound
    toEnum 4 = ResourceErrorBusy
    toEnum 5 = ResourceErrorOpenRead
    toEnum 6 = ResourceErrorOpenWrite
    toEnum 7 = ResourceErrorOpenReadWrite
    toEnum 8 = ResourceErrorClose
    toEnum 9 = ResourceErrorRead
    toEnum 10 = ResourceErrorWrite
    toEnum 11 = ResourceErrorSeek
    toEnum 12 = ResourceErrorSync
    toEnum 13 = ResourceErrorSettings
    toEnum 14 = ResourceErrorNoSpaceLeft
    toEnum 15 = ResourceErrorNotAuthorized
    toEnum 16 = ResourceErrorNumErrors
    toEnum k = AnotherResourceError k

instance P.Ord ResourceError where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

instance GErrorClass ResourceError where
    gerrorClassDomain _ = "gst-resource-error-quark"

-- | Catch exceptions of type `ResourceError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchResourceError ::
    IO a ->
    (ResourceError -> GErrorMessage -> IO a) ->
    IO a
catchResourceError = catchGErrorJustDomain

-- | Handle exceptions of type `ResourceError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleResourceError ::
    (ResourceError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleResourceError = handleGErrorJustDomain

foreign import ccall "gst_resource_error_get_type" c_gst_resource_error_get_type ::
    IO GType

instance BoxedEnum ResourceError where
    boxedEnumType _ = c_gst_resource_error_get_type

-- Enum Rank
{- |
Element priority ranks. Defines the order in which the autoplugger (or
similar rank-picking mechanisms, such as e.g. 'GI.Gst.Objects.Element.elementMakeFromUri')
will choose this element over an alternative one with the same function.

These constants serve as a rough guidance for defining the rank of a
'GI.Gst.Objects.PluginFeature.PluginFeature'. Any value is valid, including values bigger than
/@gSTRANKPRIMARY@/.
-}
data Rank =
      RankNone
    {- ^
    will be chosen last or not at all
    -}
    | RankMarginal
    {- ^
    unlikely to be chosen
    -}
    | RankSecondary
    {- ^
    likely to be chosen
    -}
    | RankPrimary
    {- ^
    will be chosen first
    -}
    | AnotherRank Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum Rank where
    fromEnum RankNone = 0
    fromEnum RankMarginal = 64
    fromEnum RankSecondary = 128
    fromEnum RankPrimary = 256
    fromEnum (AnotherRank k) = k

    toEnum 0 = RankNone
    toEnum 64 = RankMarginal
    toEnum 128 = RankSecondary
    toEnum 256 = RankPrimary
    toEnum k = AnotherRank k

instance P.Ord Rank where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_rank_get_type" c_gst_rank_get_type ::
    IO GType

instance BoxedEnum Rank where
    boxedEnumType _ = c_gst_rank_get_type

-- Enum QueryType
{- |
Standard predefined Query types
-}
data QueryType =
      QueryTypeUnknown
    {- ^
    unknown query type
    -}
    | QueryTypePosition
    {- ^
    current position in stream
    -}
    | QueryTypeDuration
    {- ^
    total duration of the stream
    -}
    | QueryTypeLatency
    {- ^
    latency of stream
    -}
    | QueryTypeJitter
    {- ^
    current jitter of stream
    -}
    | QueryTypeRate
    {- ^
    current rate of the stream
    -}
    | QueryTypeSeeking
    {- ^
    seeking capabilities
    -}
    | QueryTypeSegment
    {- ^
    segment start\/stop positions
    -}
    | QueryTypeConvert
    {- ^
    convert values between formats
    -}
    | QueryTypeFormats
    {- ^
    query supported formats for convert
    -}
    | QueryTypeBuffering
    {- ^
    query available media for efficient seeking.
    -}
    | QueryTypeCustom
    {- ^
    a custom application or element defined query.
    -}
    | QueryTypeUri
    {- ^
    query the URI of the source or sink.
    -}
    | QueryTypeAllocation
    {- ^
    the buffer allocation properties
    -}
    | QueryTypeScheduling
    {- ^
    the scheduling properties
    -}
    | QueryTypeAcceptCaps
    {- ^
    the accept caps query
    -}
    | QueryTypeCaps
    {- ^
    the caps query
    -}
    | QueryTypeDrain
    {- ^
    wait till all serialized data is consumed downstream
    -}
    | QueryTypeContext
    {- ^
    query the pipeline-local context from
        downstream or upstream (since 1.2)
    -}
    | QueryTypeBitrate
    {- ^
    the bitrate query (since 1.16)
    -}
    | AnotherQueryType Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum QueryType where
    fromEnum QueryTypeUnknown = 0
    fromEnum QueryTypePosition = 2563
    fromEnum QueryTypeDuration = 5123
    fromEnum QueryTypeLatency = 7683
    fromEnum QueryTypeJitter = 10243
    fromEnum QueryTypeRate = 12803
    fromEnum QueryTypeSeeking = 15363
    fromEnum QueryTypeSegment = 17923
    fromEnum QueryTypeConvert = 20483
    fromEnum QueryTypeFormats = 23043
    fromEnum QueryTypeBuffering = 28163
    fromEnum QueryTypeCustom = 30723
    fromEnum QueryTypeUri = 33283
    fromEnum QueryTypeAllocation = 35846
    fromEnum QueryTypeScheduling = 38401
    fromEnum QueryTypeAcceptCaps = 40963
    fromEnum QueryTypeCaps = 43523
    fromEnum QueryTypeDrain = 46086
    fromEnum QueryTypeContext = 48643
    fromEnum QueryTypeBitrate = 51202
    fromEnum (AnotherQueryType k) = k

    toEnum 0 = QueryTypeUnknown
    toEnum 2563 = QueryTypePosition
    toEnum 5123 = QueryTypeDuration
    toEnum 7683 = QueryTypeLatency
    toEnum 10243 = QueryTypeJitter
    toEnum 12803 = QueryTypeRate
    toEnum 15363 = QueryTypeSeeking
    toEnum 17923 = QueryTypeSegment
    toEnum 20483 = QueryTypeConvert
    toEnum 23043 = QueryTypeFormats
    toEnum 28163 = QueryTypeBuffering
    toEnum 30723 = QueryTypeCustom
    toEnum 33283 = QueryTypeUri
    toEnum 35846 = QueryTypeAllocation
    toEnum 38401 = QueryTypeScheduling
    toEnum 40963 = QueryTypeAcceptCaps
    toEnum 43523 = QueryTypeCaps
    toEnum 46086 = QueryTypeDrain
    toEnum 48643 = QueryTypeContext
    toEnum 51202 = QueryTypeBitrate
    toEnum k = AnotherQueryType k

instance P.Ord QueryType where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_query_type_get_type" c_gst_query_type_get_type ::
    IO GType

instance BoxedEnum QueryType where
    boxedEnumType _ = c_gst_query_type_get_type

-- Enum QOSType
{- |
The different types of QoS events that can be given to the
'GI.Gst.Structs.Event.eventNewQos' method.
-}
data QOSType =
      QOSTypeOverflow
    {- ^
    The QoS event type that is produced when upstream
       elements are producing data too quickly and the element can\'t keep up
       processing the data. Upstream should reduce their production rate. This
       type is also used when buffers arrive early or in time.
    -}
    | QOSTypeUnderflow
    {- ^
    The QoS event type that is produced when upstream
       elements are producing data too slowly and need to speed up their
       production rate.
    -}
    | QOSTypeThrottle
    {- ^
    The QoS event type that is produced when the
       application enabled throttling to limit the data rate.
    -}
    | AnotherQOSType Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum QOSType where
    fromEnum QOSTypeOverflow = 0
    fromEnum QOSTypeUnderflow = 1
    fromEnum QOSTypeThrottle = 2
    fromEnum (AnotherQOSType k) = k

    toEnum 0 = QOSTypeOverflow
    toEnum 1 = QOSTypeUnderflow
    toEnum 2 = QOSTypeThrottle
    toEnum k = AnotherQOSType k

instance P.Ord QOSType where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_qos_type_get_type" c_gst_qos_type_get_type ::
    IO GType

instance BoxedEnum QOSType where
    boxedEnumType _ = c_gst_qos_type_get_type

-- Enum PromiseResult
{- |
The result of a 'GI.Gst.Structs.Promise.Promise'

/Since: 1.14/
-}
data PromiseResult =
      PromiseResultPending
    {- ^
    Initial state. Waiting for transition to any
    	other state.
    -}
    | PromiseResultInterrupted
    {- ^
    Interrupted by the consumer as it doesn\'t
    	want the value anymore.
    -}
    | PromiseResultReplied
    {- ^
    A producer marked a reply
    -}
    | PromiseResultExpired
    {- ^
    The promise expired (the carrying object
    	lost all refs) and the promise will never be fulfilled.
    -}
    | AnotherPromiseResult Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum PromiseResult where
    fromEnum PromiseResultPending = 0
    fromEnum PromiseResultInterrupted = 1
    fromEnum PromiseResultReplied = 2
    fromEnum PromiseResultExpired = 3
    fromEnum (AnotherPromiseResult k) = k

    toEnum 0 = PromiseResultPending
    toEnum 1 = PromiseResultInterrupted
    toEnum 2 = PromiseResultReplied
    toEnum 3 = PromiseResultExpired
    toEnum k = AnotherPromiseResult k

instance P.Ord PromiseResult where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_promise_result_get_type" c_gst_promise_result_get_type ::
    IO GType

instance BoxedEnum PromiseResult where
    boxedEnumType _ = c_gst_promise_result_get_type

-- Enum ProgressType
{- |
The type of a 'GI.Gst.Flags.MessageTypeProgress'. The progress messages inform the
application of the status of asynchronous tasks.
-}
data ProgressType =
      ProgressTypeStart
    {- ^
    A new task started.
    -}
    | ProgressTypeContinue
    {- ^
    A task completed and a new one continues.
    -}
    | ProgressTypeComplete
    {- ^
    A task completed.
    -}
    | ProgressTypeCanceled
    {- ^
    A task was canceled.
    -}
    | ProgressTypeError
    {- ^
    A task caused an error. An error message is also
             posted on the bus.
    -}
    | AnotherProgressType Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum ProgressType where
    fromEnum ProgressTypeStart = 0
    fromEnum ProgressTypeContinue = 1
    fromEnum ProgressTypeComplete = 2
    fromEnum ProgressTypeCanceled = 3
    fromEnum ProgressTypeError = 4
    fromEnum (AnotherProgressType k) = k

    toEnum 0 = ProgressTypeStart
    toEnum 1 = ProgressTypeContinue
    toEnum 2 = ProgressTypeComplete
    toEnum 3 = ProgressTypeCanceled
    toEnum 4 = ProgressTypeError
    toEnum k = AnotherProgressType k

instance P.Ord ProgressType where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_progress_type_get_type" c_gst_progress_type_get_type ::
    IO GType

instance BoxedEnum ProgressType where
    boxedEnumType _ = c_gst_progress_type_get_type

-- Enum PluginError
{- |
The plugin loading errors
-}
data PluginError =
      PluginErrorModule
    {- ^
    The plugin could not be loaded
    -}
    | PluginErrorDependencies
    {- ^
    The plugin has unresolved dependencies
    -}
    | PluginErrorNameMismatch
    {- ^
    The plugin has already be loaded from a different file
    -}
    | AnotherPluginError Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum PluginError where
    fromEnum PluginErrorModule = 0
    fromEnum PluginErrorDependencies = 1
    fromEnum PluginErrorNameMismatch = 2
    fromEnum (AnotherPluginError k) = k

    toEnum 0 = PluginErrorModule
    toEnum 1 = PluginErrorDependencies
    toEnum 2 = PluginErrorNameMismatch
    toEnum k = AnotherPluginError k

instance P.Ord PluginError where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

instance GErrorClass PluginError where
    gerrorClassDomain _ = "gst_plugin_error"

-- | Catch exceptions of type `PluginError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchPluginError ::
    IO a ->
    (PluginError -> GErrorMessage -> IO a) ->
    IO a
catchPluginError = catchGErrorJustDomain

-- | Handle exceptions of type `PluginError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handlePluginError ::
    (PluginError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handlePluginError = handleGErrorJustDomain

foreign import ccall "gst_plugin_error_get_type" c_gst_plugin_error_get_type ::
    IO GType

instance BoxedEnum PluginError where
    boxedEnumType _ = c_gst_plugin_error_get_type

-- Enum ParseError
{- |
The different parsing errors that can occur.
-}
data ParseError =
      ParseErrorSyntax
    {- ^
    A syntax error occurred.
    -}
    | ParseErrorNoSuchElement
    {- ^
    The description contained an unknown element
    -}
    | ParseErrorNoSuchProperty
    {- ^
    An element did not have a specified property
    -}
    | ParseErrorLink
    {- ^
    There was an error linking two pads.
    -}
    | ParseErrorCouldNotSetProperty
    {- ^
    There was an error setting a property
    -}
    | ParseErrorEmptyBin
    {- ^
    An empty bin was specified.
    -}
    | ParseErrorEmpty
    {- ^
    An empty description was specified
    -}
    | ParseErrorDelayedLink
    {- ^
    A delayed link did not get resolved.
    -}
    | AnotherParseError Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum ParseError where
    fromEnum ParseErrorSyntax = 0
    fromEnum ParseErrorNoSuchElement = 1
    fromEnum ParseErrorNoSuchProperty = 2
    fromEnum ParseErrorLink = 3
    fromEnum ParseErrorCouldNotSetProperty = 4
    fromEnum ParseErrorEmptyBin = 5
    fromEnum ParseErrorEmpty = 6
    fromEnum ParseErrorDelayedLink = 7
    fromEnum (AnotherParseError k) = k

    toEnum 0 = ParseErrorSyntax
    toEnum 1 = ParseErrorNoSuchElement
    toEnum 2 = ParseErrorNoSuchProperty
    toEnum 3 = ParseErrorLink
    toEnum 4 = ParseErrorCouldNotSetProperty
    toEnum 5 = ParseErrorEmptyBin
    toEnum 6 = ParseErrorEmpty
    toEnum 7 = ParseErrorDelayedLink
    toEnum k = AnotherParseError k

instance P.Ord ParseError where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

instance GErrorClass ParseError where
    gerrorClassDomain _ = "gst_parse_error"

-- | Catch exceptions of type `ParseError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchParseError ::
    IO a ->
    (ParseError -> GErrorMessage -> IO a) ->
    IO a
catchParseError = catchGErrorJustDomain

-- | Handle exceptions of type `ParseError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleParseError ::
    (ParseError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleParseError = handleGErrorJustDomain

foreign import ccall "gst_parse_error_get_type" c_gst_parse_error_get_type ::
    IO GType

instance BoxedEnum ParseError where
    boxedEnumType _ = c_gst_parse_error_get_type

-- Enum PadProbeReturn
{- |
Different return values for the 'GI.Gst.Callbacks.PadProbeCallback'.
-}
data PadProbeReturn =
      PadProbeReturnDrop
    {- ^
    drop data in data probes. For push mode this means that
           the data item is not sent downstream. For pull mode, it means that
           the data item is not passed upstream. In both cases, no other probes
           are called for this item and 'GI.Gst.Enums.FlowReturnOk' or 'True' is returned to the
           caller.
    -}
    | PadProbeReturnOk
    {- ^
    normal probe return value. This leaves the probe in
           place, and defers decisions about dropping or passing data to other
           probes, if any. If there are no other probes, the default behaviour
           for the probe type applies (\'block\' for blocking probes,
           and \'pass\' for non-blocking probes).
    -}
    | PadProbeReturnRemove
    {- ^
    remove this probe.
    -}
    | PadProbeReturnPass
    {- ^
    pass the data item in the block probe and block on the
           next item.
    -}
    | PadProbeReturnHandled
    {- ^
    Data has been handled in the probe and will not be
           forwarded further. For events and buffers this is the same behaviour as
           'GI.Gst.Enums.PadProbeReturnDrop' (except that in this case you need to unref the buffer
           or event yourself). For queries it will also return 'True' to the caller.
           The probe can also modify the 'GI.Gst.Enums.FlowReturn' value by using the
           @/GST_PAD_PROBE_INFO_FLOW_RETURN/@() accessor.
           Note that the resulting query must contain valid entries.
           Since: 1.6
    -}
    | AnotherPadProbeReturn Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum PadProbeReturn where
    fromEnum PadProbeReturnDrop = 0
    fromEnum PadProbeReturnOk = 1
    fromEnum PadProbeReturnRemove = 2
    fromEnum PadProbeReturnPass = 3
    fromEnum PadProbeReturnHandled = 4
    fromEnum (AnotherPadProbeReturn k) = k

    toEnum 0 = PadProbeReturnDrop
    toEnum 1 = PadProbeReturnOk
    toEnum 2 = PadProbeReturnRemove
    toEnum 3 = PadProbeReturnPass
    toEnum 4 = PadProbeReturnHandled
    toEnum k = AnotherPadProbeReturn k

instance P.Ord PadProbeReturn where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_pad_probe_return_get_type" c_gst_pad_probe_return_get_type ::
    IO GType

instance BoxedEnum PadProbeReturn where
    boxedEnumType _ = c_gst_pad_probe_return_get_type

-- Enum PadPresence
{- |
Indicates when this pad will become available.
-}
data PadPresence =
      PadPresenceAlways
    {- ^
    the pad is always available
    -}
    | PadPresenceSometimes
    {- ^
    the pad will become available depending on the media stream
    -}
    | PadPresenceRequest
    {- ^
    the pad is only available on request with
     'GI.Gst.Objects.Element.elementRequestPad'.
    -}
    | AnotherPadPresence Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum PadPresence where
    fromEnum PadPresenceAlways = 0
    fromEnum PadPresenceSometimes = 1
    fromEnum PadPresenceRequest = 2
    fromEnum (AnotherPadPresence k) = k

    toEnum 0 = PadPresenceAlways
    toEnum 1 = PadPresenceSometimes
    toEnum 2 = PadPresenceRequest
    toEnum k = AnotherPadPresence k

instance P.Ord PadPresence where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_pad_presence_get_type" c_gst_pad_presence_get_type ::
    IO GType

instance BoxedEnum PadPresence where
    boxedEnumType _ = c_gst_pad_presence_get_type

-- Enum PadMode
{- |
The status of a GstPad. After activating a pad, which usually happens when the
parent element goes from READY to PAUSED, the GstPadMode defines if the
pad operates in push or pull mode.
-}
data PadMode =
      PadModeNone
    {- ^
    Pad will not handle dataflow
    -}
    | PadModePush
    {- ^
    Pad handles dataflow in downstream push mode
    -}
    | PadModePull
    {- ^
    Pad handles dataflow in upstream pull mode
    -}
    | AnotherPadMode Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum PadMode where
    fromEnum PadModeNone = 0
    fromEnum PadModePush = 1
    fromEnum PadModePull = 2
    fromEnum (AnotherPadMode k) = k

    toEnum 0 = PadModeNone
    toEnum 1 = PadModePush
    toEnum 2 = PadModePull
    toEnum k = AnotherPadMode k

instance P.Ord PadMode where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_pad_mode_get_type" c_gst_pad_mode_get_type ::
    IO GType

instance BoxedEnum PadMode where
    boxedEnumType _ = c_gst_pad_mode_get_type

-- Enum PadLinkReturn
{- |
Result values from gst_pad_link and friends.
-}
data PadLinkReturn =
      PadLinkReturnOk
    {- ^
    link succeeded
    -}
    | PadLinkReturnWrongHierarchy
    {- ^
    pads have no common grandparent
    -}
    | PadLinkReturnWasLinked
    {- ^
    pad was already linked
    -}
    | PadLinkReturnWrongDirection
    {- ^
    pads have wrong direction
    -}
    | PadLinkReturnNoformat
    {- ^
    pads do not have common format
    -}
    | PadLinkReturnNosched
    {- ^
    pads cannot cooperate in scheduling
    -}
    | PadLinkReturnRefused
    {- ^
    refused for some reason
    -}
    | AnotherPadLinkReturn Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum PadLinkReturn where
    fromEnum PadLinkReturnOk = 0
    fromEnum PadLinkReturnWrongHierarchy = -1
    fromEnum PadLinkReturnWasLinked = -2
    fromEnum PadLinkReturnWrongDirection = -3
    fromEnum PadLinkReturnNoformat = -4
    fromEnum PadLinkReturnNosched = -5
    fromEnum PadLinkReturnRefused = -6
    fromEnum (AnotherPadLinkReturn k) = k

    toEnum 0 = PadLinkReturnOk
    toEnum -1 = PadLinkReturnWrongHierarchy
    toEnum -2 = PadLinkReturnWasLinked
    toEnum -3 = PadLinkReturnWrongDirection
    toEnum -4 = PadLinkReturnNoformat
    toEnum -5 = PadLinkReturnNosched
    toEnum -6 = PadLinkReturnRefused
    toEnum k = AnotherPadLinkReturn k

instance P.Ord PadLinkReturn where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_pad_link_return_get_type" c_gst_pad_link_return_get_type ::
    IO GType

instance BoxedEnum PadLinkReturn where
    boxedEnumType _ = c_gst_pad_link_return_get_type

-- Enum PadDirection
{- |
The direction of a pad.
-}
data PadDirection =
      PadDirectionUnknown
    {- ^
    direction is unknown.
    -}
    | PadDirectionSrc
    {- ^
    the pad is a source pad.
    -}
    | PadDirectionSink
    {- ^
    the pad is a sink pad.
    -}
    | AnotherPadDirection Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum PadDirection where
    fromEnum PadDirectionUnknown = 0
    fromEnum PadDirectionSrc = 1
    fromEnum PadDirectionSink = 2
    fromEnum (AnotherPadDirection k) = k

    toEnum 0 = PadDirectionUnknown
    toEnum 1 = PadDirectionSrc
    toEnum 2 = PadDirectionSink
    toEnum k = AnotherPadDirection k

instance P.Ord PadDirection where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_pad_direction_get_type" c_gst_pad_direction_get_type ::
    IO GType

instance BoxedEnum PadDirection where
    boxedEnumType _ = c_gst_pad_direction_get_type

-- Enum LibraryError
{- |
Library errors are for errors from the library being used by elements
(initializing, finalizing, settings, ...)
-}
data LibraryError =
      LibraryErrorFailed
    {- ^
    a general error which doesn\'t fit in any other
    category.  Make sure you add a custom message to the error call.
    -}
    | LibraryErrorTooLazy
    {- ^
    do not use this except as a placeholder for
    deciding where to go while developing code.
    -}
    | LibraryErrorInit
    {- ^
    used when the library could not be opened.
    -}
    | LibraryErrorShutdown
    {- ^
    used when the library could not be closed.
    -}
    | LibraryErrorSettings
    {- ^
    used when the library doesn\'t accept settings.
    -}
    | LibraryErrorEncode
    {- ^
    used when the library generated an encoding error.
    -}
    | LibraryErrorNumErrors
    {- ^
    the number of library error types.
    -}
    | AnotherLibraryError Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum LibraryError where
    fromEnum LibraryErrorFailed = 1
    fromEnum LibraryErrorTooLazy = 2
    fromEnum LibraryErrorInit = 3
    fromEnum LibraryErrorShutdown = 4
    fromEnum LibraryErrorSettings = 5
    fromEnum LibraryErrorEncode = 6
    fromEnum LibraryErrorNumErrors = 7
    fromEnum (AnotherLibraryError k) = k

    toEnum 1 = LibraryErrorFailed
    toEnum 2 = LibraryErrorTooLazy
    toEnum 3 = LibraryErrorInit
    toEnum 4 = LibraryErrorShutdown
    toEnum 5 = LibraryErrorSettings
    toEnum 6 = LibraryErrorEncode
    toEnum 7 = LibraryErrorNumErrors
    toEnum k = AnotherLibraryError k

instance P.Ord LibraryError where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

instance GErrorClass LibraryError where
    gerrorClassDomain _ = "gst-library-error-quark"

-- | Catch exceptions of type `LibraryError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchLibraryError ::
    IO a ->
    (LibraryError -> GErrorMessage -> IO a) ->
    IO a
catchLibraryError = catchGErrorJustDomain

-- | Handle exceptions of type `LibraryError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleLibraryError ::
    (LibraryError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleLibraryError = handleGErrorJustDomain

foreign import ccall "gst_library_error_get_type" c_gst_library_error_get_type ::
    IO GType

instance BoxedEnum LibraryError where
    boxedEnumType _ = c_gst_library_error_get_type

-- Enum IteratorResult
{- |
The result of 'GI.Gst.Structs.Iterator.iteratorNext'.
-}
data IteratorResult =
      IteratorResultDone
    {- ^
    No more items in the iterator
    -}
    | IteratorResultOk
    {- ^
    An item was retrieved
    -}
    | IteratorResultResync
    {- ^
    Datastructure changed while iterating
    -}
    | IteratorResultError
    {- ^
    An error happened
    -}
    | AnotherIteratorResult Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum IteratorResult where
    fromEnum IteratorResultDone = 0
    fromEnum IteratorResultOk = 1
    fromEnum IteratorResultResync = 2
    fromEnum IteratorResultError = 3
    fromEnum (AnotherIteratorResult k) = k

    toEnum 0 = IteratorResultDone
    toEnum 1 = IteratorResultOk
    toEnum 2 = IteratorResultResync
    toEnum 3 = IteratorResultError
    toEnum k = AnotherIteratorResult k

instance P.Ord IteratorResult where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_iterator_result_get_type" c_gst_iterator_result_get_type ::
    IO GType

instance BoxedEnum IteratorResult where
    boxedEnumType _ = c_gst_iterator_result_get_type

-- Enum IteratorItem
{- |
The result of a 'GI.Gst.Callbacks.IteratorItemFunction'.
-}
data IteratorItem =
      IteratorItemSkip
    {- ^
    Skip this item
    -}
    | IteratorItemPass
    {- ^
    Return item
    -}
    | IteratorItemEnd
    {- ^
    Stop after this item.
    -}
    | AnotherIteratorItem Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum IteratorItem where
    fromEnum IteratorItemSkip = 0
    fromEnum IteratorItemPass = 1
    fromEnum IteratorItemEnd = 2
    fromEnum (AnotherIteratorItem k) = k

    toEnum 0 = IteratorItemSkip
    toEnum 1 = IteratorItemPass
    toEnum 2 = IteratorItemEnd
    toEnum k = AnotherIteratorItem k

instance P.Ord IteratorItem where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_iterator_item_get_type" c_gst_iterator_item_get_type ::
    IO GType

instance BoxedEnum IteratorItem where
    boxedEnumType _ = c_gst_iterator_item_get_type

-- Enum Format
{- |
Standard predefined formats
-}
data Format =
      FormatUndefined
    {- ^
    undefined format
    -}
    | FormatDefault
    {- ^
    the default format of the pad\/element. This can be
       samples for raw audio, frames\/fields for raw video (some, but not all,
       elements support this; use /@gSTFORMATTIME@/ if you don\'t have a good
       reason to query for samples\/frames)
    -}
    | FormatBytes
    {- ^
    bytes
    -}
    | FormatTime
    {- ^
    time in nanoseconds
    -}
    | FormatBuffers
    {- ^
    buffers (few, if any, elements implement this as of
        May 2009)
    -}
    | FormatPercent
    {- ^
    percentage of stream (few, if any, elements implement
        this as of May 2009)
    -}
    | AnotherFormat Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum Format where
    fromEnum FormatUndefined = 0
    fromEnum FormatDefault = 1
    fromEnum FormatBytes = 2
    fromEnum FormatTime = 3
    fromEnum FormatBuffers = 4
    fromEnum FormatPercent = 5
    fromEnum (AnotherFormat k) = k

    toEnum 0 = FormatUndefined
    toEnum 1 = FormatDefault
    toEnum 2 = FormatBytes
    toEnum 3 = FormatTime
    toEnum 4 = FormatBuffers
    toEnum 5 = FormatPercent
    toEnum k = AnotherFormat k

instance P.Ord Format where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_format_get_type" c_gst_format_get_type ::
    IO GType

instance BoxedEnum Format where
    boxedEnumType _ = c_gst_format_get_type

-- Enum FlowReturn
{- |
The result of passing data to a pad.

Note that the custom return values should not be exposed outside of the
element scope.
-}
data FlowReturn =
      FlowReturnCustomSuccess2
    {- ^
    Pre-defined custom success code.
    -}
    | FlowReturnCustomSuccess1
    {- ^
    Pre-defined custom success code (define your
                                  custom success code to this to avoid compiler
                                  warnings).
    -}
    | FlowReturnCustomSuccess
    {- ^
    Elements can use values starting from
                                  this (and higher) to define custom success
                                  codes.
    -}
    | FlowReturnOk
    {- ^
    Data passing was ok.
    -}
    | FlowReturnNotLinked
    {- ^
    Pad is not linked.
    -}
    | FlowReturnFlushing
    {- ^
    Pad is flushing.
    -}
    | FlowReturnEos
    {- ^
    Pad is EOS.
    -}
    | FlowReturnNotNegotiated
    {- ^
    Pad is not negotiated.
    -}
    | FlowReturnError
    {- ^
    Some (fatal) error occurred. Element generating
                                  this error should post an error message with more
                                  details.
    -}
    | FlowReturnNotSupported
    {- ^
    This operation is not supported.
    -}
    | FlowReturnCustomError
    {- ^
    Elements can use values starting from
                                  this (and lower) to define custom error codes.
    -}
    | FlowReturnCustomError1
    {- ^
    Pre-defined custom error code (define your
                                  custom error code to this to avoid compiler
                                  warnings).
    -}
    | FlowReturnCustomError2
    {- ^
    Pre-defined custom error code.
    -}
    | AnotherFlowReturn Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum FlowReturn where
    fromEnum FlowReturnCustomSuccess2 = 102
    fromEnum FlowReturnCustomSuccess1 = 101
    fromEnum FlowReturnCustomSuccess = 100
    fromEnum FlowReturnOk = 0
    fromEnum FlowReturnNotLinked = -1
    fromEnum FlowReturnFlushing = -2
    fromEnum FlowReturnEos = -3
    fromEnum FlowReturnNotNegotiated = -4
    fromEnum FlowReturnError = -5
    fromEnum FlowReturnNotSupported = -6
    fromEnum FlowReturnCustomError = -100
    fromEnum FlowReturnCustomError1 = -101
    fromEnum FlowReturnCustomError2 = -102
    fromEnum (AnotherFlowReturn k) = k

    toEnum 102 = FlowReturnCustomSuccess2
    toEnum 101 = FlowReturnCustomSuccess1
    toEnum 100 = FlowReturnCustomSuccess
    toEnum 0 = FlowReturnOk
    toEnum -1 = FlowReturnNotLinked
    toEnum -2 = FlowReturnFlushing
    toEnum -3 = FlowReturnEos
    toEnum -4 = FlowReturnNotNegotiated
    toEnum -5 = FlowReturnError
    toEnum -6 = FlowReturnNotSupported
    toEnum -100 = FlowReturnCustomError
    toEnum -101 = FlowReturnCustomError1
    toEnum -102 = FlowReturnCustomError2
    toEnum k = AnotherFlowReturn k

instance P.Ord FlowReturn where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_flow_return_get_type" c_gst_flow_return_get_type ::
    IO GType

instance BoxedEnum FlowReturn where
    boxedEnumType _ = c_gst_flow_return_get_type

-- Enum EventType
{- |
'GI.Gst.Enums.EventType' lists the standard event types that can be sent in a pipeline.

The custom event types can be used for private messages between elements
that can\'t be expressed using normal
GStreamer buffer passing semantics. Custom events carry an arbitrary
'GI.Gst.Structs.Structure.Structure'.
Specific custom events are distinguished by the name of the structure.
-}
data EventType =
      EventTypeUnknown
    {- ^
    unknown event.
    -}
    | EventTypeFlushStart
    {- ^
    Start a flush operation. This event clears all data
                    from the pipeline and unblock all streaming threads.
    -}
    | EventTypeFlushStop
    {- ^
    Stop a flush operation. This event resets the
                    running-time of the pipeline.
    -}
    | EventTypeStreamStart
    {- ^
    Event to mark the start of a new stream. Sent before any
                    other serialized event and only sent at the start of a new stream,
                    not after flushing seeks.
    -}
    | EventTypeCaps
    {- ^
    'GI.Gst.Structs.Caps.Caps' event. Notify the pad of a new media type.
    -}
    | EventTypeSegment
    {- ^
    A new media segment follows in the dataflow. The
                    segment events contains information for clipping buffers and
                    converting buffer timestamps to running-time and
                    stream-time.
    -}
    | EventTypeStreamCollection
    {- ^
    A new 'GI.Gst.Objects.StreamCollection.StreamCollection' is available (Since 1.10)
    -}
    | EventTypeTag
    {- ^
    A new set of metadata tags has been found in the stream.
    -}
    | EventTypeBuffersize
    {- ^
    Notification of buffering requirements. Currently not
                    used yet.
    -}
    | EventTypeSinkMessage
    {- ^
    An event that sinks turn into a message. Used to
                             send messages that should be emitted in sync with
                             rendering.
    -}
    | EventTypeStreamGroupDone
    {- ^
    Indicates that there is no more data for
                    the stream group ID in the message. Sent before EOS
                    in some instances and should be handled mostly the same. (Since 1.10)
    -}
    | EventTypeEos
    {- ^
    End-Of-Stream. No more data is to be expected to follow
                    without either a STREAM_START event, or a FLUSH_STOP and a SEGMENT
                    event.
    -}
    | EventTypeToc
    {- ^
    An event which indicates that a new table of contents (TOC)
                    was found or updated.
    -}
    | EventTypeProtection
    {- ^
    An event which indicates that new or updated
                    encryption information has been found in the stream.
    -}
    | EventTypeSegmentDone
    {- ^
    Marks the end of a segment playback.
    -}
    | EventTypeGap
    {- ^
    Marks a gap in the datastream.
    -}
    | EventTypeQos
    {- ^
    A quality message. Used to indicate to upstream elements
                    that the downstream elements should adjust their processing
                    rate.
    -}
    | EventTypeSeek
    {- ^
    A request for a new playback position and rate.
    -}
    | EventTypeNavigation
    {- ^
    Navigation events are usually used for communicating
                           user requests, such as mouse or keyboard movements,
                           to upstream elements.
    -}
    | EventTypeLatency
    {- ^
    Notification of new latency adjustment. Sinks will use
                        the latency information to adjust their synchronisation.
    -}
    | EventTypeStep
    {- ^
    A request for stepping through the media. Sinks will usually
                     execute the step operation.
    -}
    | EventTypeReconfigure
    {- ^
    A request for upstream renegotiating caps and reconfiguring.
    -}
    | EventTypeTocSelect
    {- ^
    A request for a new playback position based on TOC
                           entry\'s UID.
    -}
    | EventTypeSelectStreams
    {- ^
    A request to select one or more streams (Since 1.10)
    -}
    | EventTypeCustomUpstream
    {- ^
    Upstream custom event
    -}
    | EventTypeCustomDownstream
    {- ^
    Downstream custom event that travels in the
                           data flow.
    -}
    | EventTypeCustomDownstreamOob
    {- ^
    Custom out-of-band downstream event.
    -}
    | EventTypeCustomDownstreamSticky
    {- ^
    Custom sticky downstream event.
    -}
    | EventTypeCustomBoth
    {- ^
    Custom upstream or downstream event.
                            In-band when travelling downstream.
    -}
    | EventTypeCustomBothOob
    {- ^
    Custom upstream or downstream out-of-band event.
    -}
    | AnotherEventType Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum EventType where
    fromEnum EventTypeUnknown = 0
    fromEnum EventTypeFlushStart = 2563
    fromEnum EventTypeFlushStop = 5127
    fromEnum EventTypeStreamStart = 10254
    fromEnum EventTypeCaps = 12814
    fromEnum EventTypeSegment = 17934
    fromEnum EventTypeStreamCollection = 19230
    fromEnum EventTypeTag = 20510
    fromEnum EventTypeBuffersize = 23054
    fromEnum EventTypeSinkMessage = 25630
    fromEnum EventTypeStreamGroupDone = 26894
    fromEnum EventTypeEos = 28174
    fromEnum EventTypeToc = 30750
    fromEnum EventTypeProtection = 33310
    fromEnum EventTypeSegmentDone = 38406
    fromEnum EventTypeGap = 40966
    fromEnum EventTypeQos = 48641
    fromEnum EventTypeSeek = 51201
    fromEnum EventTypeNavigation = 53761
    fromEnum EventTypeLatency = 56321
    fromEnum EventTypeStep = 58881
    fromEnum EventTypeReconfigure = 61441
    fromEnum EventTypeTocSelect = 64001
    fromEnum EventTypeSelectStreams = 66561
    fromEnum EventTypeCustomUpstream = 69121
    fromEnum EventTypeCustomDownstream = 71686
    fromEnum EventTypeCustomDownstreamOob = 74242
    fromEnum EventTypeCustomDownstreamSticky = 76830
    fromEnum EventTypeCustomBoth = 79367
    fromEnum EventTypeCustomBothOob = 81923
    fromEnum (AnotherEventType k) = k

    toEnum 0 = EventTypeUnknown
    toEnum 2563 = EventTypeFlushStart
    toEnum 5127 = EventTypeFlushStop
    toEnum 10254 = EventTypeStreamStart
    toEnum 12814 = EventTypeCaps
    toEnum 17934 = EventTypeSegment
    toEnum 19230 = EventTypeStreamCollection
    toEnum 20510 = EventTypeTag
    toEnum 23054 = EventTypeBuffersize
    toEnum 25630 = EventTypeSinkMessage
    toEnum 26894 = EventTypeStreamGroupDone
    toEnum 28174 = EventTypeEos
    toEnum 30750 = EventTypeToc
    toEnum 33310 = EventTypeProtection
    toEnum 38406 = EventTypeSegmentDone
    toEnum 40966 = EventTypeGap
    toEnum 48641 = EventTypeQos
    toEnum 51201 = EventTypeSeek
    toEnum 53761 = EventTypeNavigation
    toEnum 56321 = EventTypeLatency
    toEnum 58881 = EventTypeStep
    toEnum 61441 = EventTypeReconfigure
    toEnum 64001 = EventTypeTocSelect
    toEnum 66561 = EventTypeSelectStreams
    toEnum 69121 = EventTypeCustomUpstream
    toEnum 71686 = EventTypeCustomDownstream
    toEnum 74242 = EventTypeCustomDownstreamOob
    toEnum 76830 = EventTypeCustomDownstreamSticky
    toEnum 79367 = EventTypeCustomBoth
    toEnum 81923 = EventTypeCustomBothOob
    toEnum k = AnotherEventType k

instance P.Ord EventType where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_event_type_get_type" c_gst_event_type_get_type ::
    IO GType

instance BoxedEnum EventType where
    boxedEnumType _ = c_gst_event_type_get_type

-- Enum DebugLevel
{- |
The level defines the importance of a debugging message. The more important a
message is, the greater the probability that the debugging system outputs it.
-}
data DebugLevel =
      DebugLevelNone
    {- ^
    No debugging level specified or desired. Used to deactivate
     debugging output.
    -}
    | DebugLevelError
    {- ^
    Error messages are to be used only when an error occurred
     that stops the application from keeping working correctly.
     An examples is gst_element_error, which outputs a message with this priority.
     It does not mean that the application is terminating as with g_error.
    -}
    | DebugLevelWarning
    {- ^
    Warning messages are to inform about abnormal behaviour
     that could lead to problems or weird behaviour later on. An example of this
     would be clocking issues (\"your computer is pretty slow\") or broken input
     data (\"Can\'t synchronize to stream.\")
    -}
    | DebugLevelFixme
    {- ^
    Fixme messages are messages that indicate that something
     in the executed code path is not fully implemented or handled yet. Note
     that this does not replace proper error handling in any way, the purpose
     of this message is to make it easier to spot incomplete\/unfinished pieces
     of code when reading the debug log.
    -}
    | DebugLevelInfo
    {- ^
    Informational messages should be used to keep the developer
     updated about what is happening.
     Examples where this should be used are when a typefind function has
     successfully determined the type of the stream or when an mp3 plugin detects
     the format to be used. (\"This file has mono sound.\")
    -}
    | DebugLevelDebug
    {- ^
    Debugging messages should be used when something common
     happens that is not the expected default behavior, or something that\'s
     useful to know but doesn\'t happen all the time (ie. per loop iteration or
     buffer processed or event handled).
     An example would be notifications about state changes or receiving\/sending
     of events.
    -}
    | DebugLevelLog
    {- ^
    Log messages are messages that are very common but might be
     useful to know. As a rule of thumb a pipeline that is running as expected
     should never output anything else but LOG messages whilst processing data.
     Use this log level to log recurring information in chain functions and
     loop functions, for example.
    -}
    | DebugLevelTrace
    {- ^
    Tracing-related messages.
     Examples for this are referencing\/dereferencing of objects.
    -}
    | DebugLevelMemdump
    {- ^
    memory dump messages are used to log (small) chunks of
     data as memory dumps in the log. They will be displayed as hexdump with
     ASCII characters.
    -}
    | DebugLevelCount
    {- ^
    The number of defined debugging levels.
    -}
    | AnotherDebugLevel Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum DebugLevel where
    fromEnum DebugLevelNone = 0
    fromEnum DebugLevelError = 1
    fromEnum DebugLevelWarning = 2
    fromEnum DebugLevelFixme = 3
    fromEnum DebugLevelInfo = 4
    fromEnum DebugLevelDebug = 5
    fromEnum DebugLevelLog = 6
    fromEnum DebugLevelTrace = 7
    fromEnum DebugLevelMemdump = 9
    fromEnum DebugLevelCount = 10
    fromEnum (AnotherDebugLevel k) = k

    toEnum 0 = DebugLevelNone
    toEnum 1 = DebugLevelError
    toEnum 2 = DebugLevelWarning
    toEnum 3 = DebugLevelFixme
    toEnum 4 = DebugLevelInfo
    toEnum 5 = DebugLevelDebug
    toEnum 6 = DebugLevelLog
    toEnum 7 = DebugLevelTrace
    toEnum 9 = DebugLevelMemdump
    toEnum 10 = DebugLevelCount
    toEnum k = AnotherDebugLevel k

instance P.Ord DebugLevel where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_debug_level_get_type" c_gst_debug_level_get_type ::
    IO GType

instance BoxedEnum DebugLevel where
    boxedEnumType _ = c_gst_debug_level_get_type

-- Enum DebugColorMode
{- |
/No description available in the introspection data./
-}
data DebugColorMode =
      DebugColorModeOff
    {- ^
    Do not use colors in logs.
    -}
    | DebugColorModeOn
    {- ^
    Paint logs in a platform-specific way.
    -}
    | DebugColorModeUnix
    {- ^
    Paint logs with UNIX terminal color codes
                                no matter what platform GStreamer is running on.
    -}
    | AnotherDebugColorMode Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum DebugColorMode where
    fromEnum DebugColorModeOff = 0
    fromEnum DebugColorModeOn = 1
    fromEnum DebugColorModeUnix = 2
    fromEnum (AnotherDebugColorMode k) = k

    toEnum 0 = DebugColorModeOff
    toEnum 1 = DebugColorModeOn
    toEnum 2 = DebugColorModeUnix
    toEnum k = AnotherDebugColorMode k

instance P.Ord DebugColorMode where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_debug_color_mode_get_type" c_gst_debug_color_mode_get_type ::
    IO GType

instance BoxedEnum DebugColorMode where
    boxedEnumType _ = c_gst_debug_color_mode_get_type

-- Enum CoreError
{- |
Core errors are errors inside the core GStreamer library.
-}
data CoreError =
      CoreErrorFailed
    {- ^
    a general error which doesn\'t fit in any other
    category.  Make sure you add a custom message to the error call.
    -}
    | CoreErrorTooLazy
    {- ^
    do not use this except as a placeholder for
    deciding where to go while developing code.
    -}
    | CoreErrorNotImplemented
    {- ^
    use this when you do not want to implement
    this functionality yet.
    -}
    | CoreErrorStateChange
    {- ^
    used for state change errors.
    -}
    | CoreErrorPad
    {- ^
    used for pad-related errors.
    -}
    | CoreErrorThread
    {- ^
    used for thread-related errors.
    -}
    | CoreErrorNegotiation
    {- ^
    used for negotiation-related errors.
    -}
    | CoreErrorEvent
    {- ^
    used for event-related errors.
    -}
    | CoreErrorSeek
    {- ^
    used for seek-related errors.
    -}
    | CoreErrorCaps
    {- ^
    used for caps-related errors.
    -}
    | CoreErrorTag
    {- ^
    used for negotiation-related errors.
    -}
    | CoreErrorMissingPlugin
    {- ^
    used if a plugin is missing.
    -}
    | CoreErrorClock
    {- ^
    used for clock related errors.
    -}
    | CoreErrorDisabled
    {- ^
    used if functionality has been disabled at
                              compile time.
    -}
    | CoreErrorNumErrors
    {- ^
    the number of core error types.
    -}
    | AnotherCoreError Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum CoreError where
    fromEnum CoreErrorFailed = 1
    fromEnum CoreErrorTooLazy = 2
    fromEnum CoreErrorNotImplemented = 3
    fromEnum CoreErrorStateChange = 4
    fromEnum CoreErrorPad = 5
    fromEnum CoreErrorThread = 6
    fromEnum CoreErrorNegotiation = 7
    fromEnum CoreErrorEvent = 8
    fromEnum CoreErrorSeek = 9
    fromEnum CoreErrorCaps = 10
    fromEnum CoreErrorTag = 11
    fromEnum CoreErrorMissingPlugin = 12
    fromEnum CoreErrorClock = 13
    fromEnum CoreErrorDisabled = 14
    fromEnum CoreErrorNumErrors = 15
    fromEnum (AnotherCoreError k) = k

    toEnum 1 = CoreErrorFailed
    toEnum 2 = CoreErrorTooLazy
    toEnum 3 = CoreErrorNotImplemented
    toEnum 4 = CoreErrorStateChange
    toEnum 5 = CoreErrorPad
    toEnum 6 = CoreErrorThread
    toEnum 7 = CoreErrorNegotiation
    toEnum 8 = CoreErrorEvent
    toEnum 9 = CoreErrorSeek
    toEnum 10 = CoreErrorCaps
    toEnum 11 = CoreErrorTag
    toEnum 12 = CoreErrorMissingPlugin
    toEnum 13 = CoreErrorClock
    toEnum 14 = CoreErrorDisabled
    toEnum 15 = CoreErrorNumErrors
    toEnum k = AnotherCoreError k

instance P.Ord CoreError where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

instance GErrorClass CoreError where
    gerrorClassDomain _ = "gst-core-error-quark"

-- | Catch exceptions of type `CoreError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchCoreError ::
    IO a ->
    (CoreError -> GErrorMessage -> IO a) ->
    IO a
catchCoreError = catchGErrorJustDomain

-- | Handle exceptions of type `CoreError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleCoreError ::
    (CoreError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleCoreError = handleGErrorJustDomain

foreign import ccall "gst_core_error_get_type" c_gst_core_error_get_type ::
    IO GType

instance BoxedEnum CoreError where
    boxedEnumType _ = c_gst_core_error_get_type

-- Enum ClockType
{- |
The different kind of clocks.
-}
data ClockType =
      ClockTypeRealtime
    {- ^
    time since Epoch
    -}
    | ClockTypeMonotonic
    {- ^
    monotonic time since some unspecified starting
                               point
    -}
    | ClockTypeOther
    {- ^
    some other time source is used (Since 1.0.5)
    -}
    | AnotherClockType Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum ClockType where
    fromEnum ClockTypeRealtime = 0
    fromEnum ClockTypeMonotonic = 1
    fromEnum ClockTypeOther = 2
    fromEnum (AnotherClockType k) = k

    toEnum 0 = ClockTypeRealtime
    toEnum 1 = ClockTypeMonotonic
    toEnum 2 = ClockTypeOther
    toEnum k = AnotherClockType k

instance P.Ord ClockType where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_clock_type_get_type" c_gst_clock_type_get_type ::
    IO GType

instance BoxedEnum ClockType where
    boxedEnumType _ = c_gst_clock_type_get_type

-- Enum ClockReturn
{- |
The return value of a clock operation.
-}
data ClockReturn =
      ClockReturnOk
    {- ^
    The operation succeeded.
    -}
    | ClockReturnEarly
    {- ^
    The operation was scheduled too late.
    -}
    | ClockReturnUnscheduled
    {- ^
    The clockID was unscheduled
    -}
    | ClockReturnBusy
    {- ^
    The ClockID is busy
    -}
    | ClockReturnBadtime
    {- ^
    A bad time was provided to a function.
    -}
    | ClockReturnError
    {- ^
    An error occurred
    -}
    | ClockReturnUnsupported
    {- ^
    Operation is not supported
    -}
    | ClockReturnDone
    {- ^
    The ClockID is done waiting
    -}
    | AnotherClockReturn Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum ClockReturn where
    fromEnum ClockReturnOk = 0
    fromEnum ClockReturnEarly = 1
    fromEnum ClockReturnUnscheduled = 2
    fromEnum ClockReturnBusy = 3
    fromEnum ClockReturnBadtime = 4
    fromEnum ClockReturnError = 5
    fromEnum ClockReturnUnsupported = 6
    fromEnum ClockReturnDone = 7
    fromEnum (AnotherClockReturn k) = k

    toEnum 0 = ClockReturnOk
    toEnum 1 = ClockReturnEarly
    toEnum 2 = ClockReturnUnscheduled
    toEnum 3 = ClockReturnBusy
    toEnum 4 = ClockReturnBadtime
    toEnum 5 = ClockReturnError
    toEnum 6 = ClockReturnUnsupported
    toEnum 7 = ClockReturnDone
    toEnum k = AnotherClockReturn k

instance P.Ord ClockReturn where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_clock_return_get_type" c_gst_clock_return_get_type ::
    IO GType

instance BoxedEnum ClockReturn where
    boxedEnumType _ = c_gst_clock_return_get_type

-- Enum ClockEntryType
{- |
The type of the clock entry
-}
data ClockEntryType =
      ClockEntryTypeSingle
    {- ^
    a single shot timeout
    -}
    | ClockEntryTypePeriodic
    {- ^
    a periodic timeout request
    -}
    | AnotherClockEntryType Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum ClockEntryType where
    fromEnum ClockEntryTypeSingle = 0
    fromEnum ClockEntryTypePeriodic = 1
    fromEnum (AnotherClockEntryType k) = k

    toEnum 0 = ClockEntryTypeSingle
    toEnum 1 = ClockEntryTypePeriodic
    toEnum k = AnotherClockEntryType k

instance P.Ord ClockEntryType where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_clock_entry_type_get_type" c_gst_clock_entry_type_get_type ::
    IO GType

instance BoxedEnum ClockEntryType where
    boxedEnumType _ = c_gst_clock_entry_type_get_type

-- Enum CapsIntersectMode
{- |
Modes of caps intersection

/@gSTCAPSINTERSECTZIGZAG@/ tries to preserve overall order of both caps
by iterating on the caps\' structures as the following matrix shows:
>
>         caps1
>      +-------------
>      | 1  2  4  7
>caps2 | 3  5  8 10
>      | 6  9 11 12

Used when there is no explicit precedence of one caps over the other. e.g.
tee\'s sink pad getcaps function, it will probe its src pad peers\' for their
caps and intersect them with this mode.

/@gSTCAPSINTERSECTFIRST@/ is useful when an element wants to preserve
another element\'s caps priority order when intersecting with its own caps.
Example: If caps1 is [A, B, C] and caps2 is [E, B, D, A], the result
would be [A, B], maintaining the first caps priority on the intersection.
-}
data CapsIntersectMode =
      CapsIntersectModeZigZag
    {- ^
    Zig-zags over both caps.
    -}
    | CapsIntersectModeFirst
    {- ^
    Keeps the first caps order.
    -}
    | AnotherCapsIntersectMode Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum CapsIntersectMode where
    fromEnum CapsIntersectModeZigZag = 0
    fromEnum CapsIntersectModeFirst = 1
    fromEnum (AnotherCapsIntersectMode k) = k

    toEnum 0 = CapsIntersectModeZigZag
    toEnum 1 = CapsIntersectModeFirst
    toEnum k = AnotherCapsIntersectMode k

instance P.Ord CapsIntersectMode where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_caps_intersect_mode_get_type" c_gst_caps_intersect_mode_get_type ::
    IO GType

instance BoxedEnum CapsIntersectMode where
    boxedEnumType _ = c_gst_caps_intersect_mode_get_type

-- Enum BusSyncReply
{- |
The result values for a GstBusSyncHandler.
-}
data BusSyncReply =
      BusSyncReplyDrop
    {- ^
    drop the message
    -}
    | BusSyncReplyPass
    {- ^
    pass the message to the async queue
    -}
    | BusSyncReplyAsync
    {- ^
    pass message to async queue, continue if message is handled
    -}
    | AnotherBusSyncReply Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum BusSyncReply where
    fromEnum BusSyncReplyDrop = 0
    fromEnum BusSyncReplyPass = 1
    fromEnum BusSyncReplyAsync = 2
    fromEnum (AnotherBusSyncReply k) = k

    toEnum 0 = BusSyncReplyDrop
    toEnum 1 = BusSyncReplyPass
    toEnum 2 = BusSyncReplyAsync
    toEnum k = AnotherBusSyncReply k

instance P.Ord BusSyncReply where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_bus_sync_reply_get_type" c_gst_bus_sync_reply_get_type ::
    IO GType

instance BoxedEnum BusSyncReply where
    boxedEnumType _ = c_gst_bus_sync_reply_get_type

-- Enum BufferingMode
{- |
The different types of buffering methods.
-}
data BufferingMode =
      BufferingModeStream
    {- ^
    a small amount of data is buffered
    -}
    | BufferingModeDownload
    {- ^
    the stream is being downloaded
    -}
    | BufferingModeTimeshift
    {- ^
    the stream is being downloaded in a ringbuffer
    -}
    | BufferingModeLive
    {- ^
    the stream is a live stream
    -}
    | AnotherBufferingMode Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum BufferingMode where
    fromEnum BufferingModeStream = 0
    fromEnum BufferingModeDownload = 1
    fromEnum BufferingModeTimeshift = 2
    fromEnum BufferingModeLive = 3
    fromEnum (AnotherBufferingMode k) = k

    toEnum 0 = BufferingModeStream
    toEnum 1 = BufferingModeDownload
    toEnum 2 = BufferingModeTimeshift
    toEnum 3 = BufferingModeLive
    toEnum k = AnotherBufferingMode k

instance P.Ord BufferingMode where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "gst_buffering_mode_get_type" c_gst_buffering_mode_get_type ::
    IO GType

instance BoxedEnum BufferingMode where
    boxedEnumType _ = c_gst_buffering_mode_get_type