{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.HarfBuzz.Structs.FeatureT.FeatureT' is the structure that holds information about requested
-- feature application. The feature will be applied with the given value to all
-- glyphs which are in clusters between /@start@/ (inclusive) and /@end@/ (exclusive).
-- Setting start to /@hBFEATUREGLOBALSTART@/ and end to /@hBFEATUREGLOBALEND@/
-- specifies that the feature always applies to the entire buffer.

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

module GI.HarfBuzz.Structs.FeatureT
    ( 

-- * Exported types
    FeatureT(..)                            ,
    newZeroFeatureT                         ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveFeatureTMethod                   ,
#endif



 -- * Properties


-- ** end #attr:end#
-- | the cluster to end applying this feature setting (exclusive).

#if defined(ENABLE_OVERLOADING)
    featureT_end                            ,
#endif
    getFeatureTEnd                          ,
    setFeatureTEnd                          ,


-- ** start #attr:start#
-- | the cluster to start applying this feature setting (inclusive).

#if defined(ENABLE_OVERLOADING)
    featureT_start                          ,
#endif
    getFeatureTStart                        ,
    setFeatureTStart                        ,


-- ** tag #attr:tag#
-- | a feature tag

#if defined(ENABLE_OVERLOADING)
    featureT_tag                            ,
#endif
    getFeatureTTag                          ,
    setFeatureTTag                          ,


-- ** value #attr:value#
-- | 0 disables the feature, non-zero (usually 1) enables the feature.
-- For features implemented as lookup type 3 (like \'salt\') the /@value@/ is a one
-- based index into the alternates.

#if defined(ENABLE_OVERLOADING)
    featureT_value                          ,
#endif
    getFeatureTValue                        ,
    setFeatureTValue                        ,




    ) 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
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.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
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
import qualified GHC.Records as R


-- | Memory-managed wrapper type.
newtype FeatureT = FeatureT (SP.ManagedPtr FeatureT)
    deriving (FeatureT -> FeatureT -> Bool
(FeatureT -> FeatureT -> Bool)
-> (FeatureT -> FeatureT -> Bool) -> Eq FeatureT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FeatureT -> FeatureT -> Bool
$c/= :: FeatureT -> FeatureT -> Bool
== :: FeatureT -> FeatureT -> Bool
$c== :: FeatureT -> FeatureT -> Bool
Eq)

instance SP.ManagedPtrNewtype FeatureT where
    toManagedPtr :: FeatureT -> ManagedPtr FeatureT
toManagedPtr (FeatureT ManagedPtr FeatureT
p) = ManagedPtr FeatureT
p

foreign import ccall "hb_gobject_feature_get_type" c_hb_gobject_feature_get_type :: 
    IO GType

type instance O.ParentTypes FeatureT = '[]
instance O.HasParentTypes FeatureT

instance B.Types.TypedObject FeatureT where
    glibType :: IO GType
glibType = IO GType
c_hb_gobject_feature_get_type

instance B.Types.GBoxed FeatureT

-- | Convert 'FeatureT' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe FeatureT) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_hb_gobject_feature_get_type
    gvalueSet_ :: Ptr GValue -> Maybe FeatureT -> IO ()
gvalueSet_ Ptr GValue
gv Maybe FeatureT
P.Nothing = Ptr GValue -> Ptr FeatureT -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr FeatureT
forall a. Ptr a
FP.nullPtr :: FP.Ptr FeatureT)
    gvalueSet_ Ptr GValue
gv (P.Just FeatureT
obj) = FeatureT -> (Ptr FeatureT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FeatureT
obj (Ptr GValue -> Ptr FeatureT -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe FeatureT)
gvalueGet_ Ptr GValue
gv = do
        Ptr FeatureT
ptr <- Ptr GValue -> IO (Ptr FeatureT)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr FeatureT)
        if Ptr FeatureT
ptr Ptr FeatureT -> Ptr FeatureT -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr FeatureT
forall a. Ptr a
FP.nullPtr
        then FeatureT -> Maybe FeatureT
forall a. a -> Maybe a
P.Just (FeatureT -> Maybe FeatureT) -> IO FeatureT -> IO (Maybe FeatureT)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr FeatureT -> FeatureT) -> Ptr FeatureT -> IO FeatureT
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr FeatureT -> FeatureT
FeatureT Ptr FeatureT
ptr
        else Maybe FeatureT -> IO (Maybe FeatureT)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FeatureT
forall a. Maybe a
P.Nothing
        
    

-- | Construct a `FeatureT` struct initialized to zero.
newZeroFeatureT :: MonadIO m => m FeatureT
newZeroFeatureT :: forall (m :: * -> *). MonadIO m => m FeatureT
newZeroFeatureT = IO FeatureT -> m FeatureT
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FeatureT -> m FeatureT) -> IO FeatureT -> m FeatureT
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr FeatureT)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
16 IO (Ptr FeatureT) -> (Ptr FeatureT -> IO FeatureT) -> IO FeatureT
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr FeatureT -> FeatureT) -> Ptr FeatureT -> IO FeatureT
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr FeatureT -> FeatureT
FeatureT

instance tag ~ 'AttrSet => Constructible FeatureT tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr FeatureT -> FeatureT)
-> [AttrOp FeatureT tag] -> m FeatureT
new ManagedPtr FeatureT -> FeatureT
_ [AttrOp FeatureT tag]
attrs = do
        FeatureT
o <- m FeatureT
forall (m :: * -> *). MonadIO m => m FeatureT
newZeroFeatureT
        FeatureT -> [AttrOp FeatureT 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set FeatureT
o [AttrOp FeatureT tag]
[AttrOp FeatureT 'AttrSet]
attrs
        FeatureT -> m FeatureT
forall (m :: * -> *) a. Monad m => a -> m a
return FeatureT
o


-- | Get the value of the “@tag@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' featureT #tag
-- @
getFeatureTTag :: MonadIO m => FeatureT -> m Word32
getFeatureTTag :: forall (m :: * -> *). MonadIO m => FeatureT -> m Word32
getFeatureTTag FeatureT
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ FeatureT -> (Ptr FeatureT -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FeatureT
s ((Ptr FeatureT -> IO Word32) -> IO Word32)
-> (Ptr FeatureT -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr FeatureT
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr FeatureT
ptr Ptr FeatureT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@tag@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' featureT [ #tag 'Data.GI.Base.Attributes.:=' value ]
-- @
setFeatureTTag :: MonadIO m => FeatureT -> Word32 -> m ()
setFeatureTTag :: forall (m :: * -> *). MonadIO m => FeatureT -> Word32 -> m ()
setFeatureTTag FeatureT
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FeatureT -> (Ptr FeatureT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FeatureT
s ((Ptr FeatureT -> IO ()) -> IO ())
-> (Ptr FeatureT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr FeatureT
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr FeatureT
ptr Ptr FeatureT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data FeatureTTagFieldInfo
instance AttrInfo FeatureTTagFieldInfo where
    type AttrBaseTypeConstraint FeatureTTagFieldInfo = (~) FeatureT
    type AttrAllowedOps FeatureTTagFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint FeatureTTagFieldInfo = (~) Word32
    type AttrTransferTypeConstraint FeatureTTagFieldInfo = (~)Word32
    type AttrTransferType FeatureTTagFieldInfo = Word32
    type AttrGetType FeatureTTagFieldInfo = Word32
    type AttrLabel FeatureTTagFieldInfo = "tag"
    type AttrOrigin FeatureTTagFieldInfo = FeatureT
    attrGet = getFeatureTTag
    attrSet = setFeatureTTag
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

featureT_tag :: AttrLabelProxy "tag"
featureT_tag = AttrLabelProxy

#endif


-- | Get the value of the “@value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' featureT #value
-- @
getFeatureTValue :: MonadIO m => FeatureT -> m Word32
getFeatureTValue :: forall (m :: * -> *). MonadIO m => FeatureT -> m Word32
getFeatureTValue FeatureT
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ FeatureT -> (Ptr FeatureT -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FeatureT
s ((Ptr FeatureT -> IO Word32) -> IO Word32)
-> (Ptr FeatureT -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr FeatureT
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr FeatureT
ptr Ptr FeatureT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' featureT [ #value 'Data.GI.Base.Attributes.:=' value ]
-- @
setFeatureTValue :: MonadIO m => FeatureT -> Word32 -> m ()
setFeatureTValue :: forall (m :: * -> *). MonadIO m => FeatureT -> Word32 -> m ()
setFeatureTValue FeatureT
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FeatureT -> (Ptr FeatureT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FeatureT
s ((Ptr FeatureT -> IO ()) -> IO ())
-> (Ptr FeatureT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr FeatureT
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr FeatureT
ptr Ptr FeatureT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data FeatureTValueFieldInfo
instance AttrInfo FeatureTValueFieldInfo where
    type AttrBaseTypeConstraint FeatureTValueFieldInfo = (~) FeatureT
    type AttrAllowedOps FeatureTValueFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint FeatureTValueFieldInfo = (~) Word32
    type AttrTransferTypeConstraint FeatureTValueFieldInfo = (~)Word32
    type AttrTransferType FeatureTValueFieldInfo = Word32
    type AttrGetType FeatureTValueFieldInfo = Word32
    type AttrLabel FeatureTValueFieldInfo = "value"
    type AttrOrigin FeatureTValueFieldInfo = FeatureT
    attrGet = getFeatureTValue
    attrSet = setFeatureTValue
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

featureT_value :: AttrLabelProxy "value"
featureT_value = AttrLabelProxy

#endif


-- | Get the value of the “@start@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' featureT #start
-- @
getFeatureTStart :: MonadIO m => FeatureT -> m Word32
getFeatureTStart :: forall (m :: * -> *). MonadIO m => FeatureT -> m Word32
getFeatureTStart FeatureT
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ FeatureT -> (Ptr FeatureT -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FeatureT
s ((Ptr FeatureT -> IO Word32) -> IO Word32)
-> (Ptr FeatureT -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr FeatureT
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr FeatureT
ptr Ptr FeatureT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@start@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' featureT [ #start 'Data.GI.Base.Attributes.:=' value ]
-- @
setFeatureTStart :: MonadIO m => FeatureT -> Word32 -> m ()
setFeatureTStart :: forall (m :: * -> *). MonadIO m => FeatureT -> Word32 -> m ()
setFeatureTStart FeatureT
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FeatureT -> (Ptr FeatureT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FeatureT
s ((Ptr FeatureT -> IO ()) -> IO ())
-> (Ptr FeatureT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr FeatureT
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr FeatureT
ptr Ptr FeatureT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data FeatureTStartFieldInfo
instance AttrInfo FeatureTStartFieldInfo where
    type AttrBaseTypeConstraint FeatureTStartFieldInfo = (~) FeatureT
    type AttrAllowedOps FeatureTStartFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint FeatureTStartFieldInfo = (~) Word32
    type AttrTransferTypeConstraint FeatureTStartFieldInfo = (~)Word32
    type AttrTransferType FeatureTStartFieldInfo = Word32
    type AttrGetType FeatureTStartFieldInfo = Word32
    type AttrLabel FeatureTStartFieldInfo = "start"
    type AttrOrigin FeatureTStartFieldInfo = FeatureT
    attrGet = getFeatureTStart
    attrSet = setFeatureTStart
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

featureT_start :: AttrLabelProxy "start"
featureT_start = AttrLabelProxy

#endif


-- | Get the value of the “@end@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' featureT #end
-- @
getFeatureTEnd :: MonadIO m => FeatureT -> m Word32
getFeatureTEnd :: forall (m :: * -> *). MonadIO m => FeatureT -> m Word32
getFeatureTEnd FeatureT
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ FeatureT -> (Ptr FeatureT -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FeatureT
s ((Ptr FeatureT -> IO Word32) -> IO Word32)
-> (Ptr FeatureT -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr FeatureT
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr FeatureT
ptr Ptr FeatureT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@end@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' featureT [ #end 'Data.GI.Base.Attributes.:=' value ]
-- @
setFeatureTEnd :: MonadIO m => FeatureT -> Word32 -> m ()
setFeatureTEnd :: forall (m :: * -> *). MonadIO m => FeatureT -> Word32 -> m ()
setFeatureTEnd FeatureT
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FeatureT -> (Ptr FeatureT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FeatureT
s ((Ptr FeatureT -> IO ()) -> IO ())
-> (Ptr FeatureT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr FeatureT
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr FeatureT
ptr Ptr FeatureT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data FeatureTEndFieldInfo
instance AttrInfo FeatureTEndFieldInfo where
    type AttrBaseTypeConstraint FeatureTEndFieldInfo = (~) FeatureT
    type AttrAllowedOps FeatureTEndFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint FeatureTEndFieldInfo = (~) Word32
    type AttrTransferTypeConstraint FeatureTEndFieldInfo = (~)Word32
    type AttrTransferType FeatureTEndFieldInfo = Word32
    type AttrGetType FeatureTEndFieldInfo = Word32
    type AttrLabel FeatureTEndFieldInfo = "end"
    type AttrOrigin FeatureTEndFieldInfo = FeatureT
    attrGet = getFeatureTEnd
    attrSet = setFeatureTEnd
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

featureT_end :: AttrLabelProxy "end"
featureT_end = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FeatureT
type instance O.AttributeList FeatureT = FeatureTAttributeList
type FeatureTAttributeList = ('[ '("tag", FeatureTTagFieldInfo), '("value", FeatureTValueFieldInfo), '("start", FeatureTStartFieldInfo), '("end", FeatureTEndFieldInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveFeatureTMethod (t :: Symbol) (o :: *) :: * where
    ResolveFeatureTMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveFeatureTMethod t FeatureT, O.OverloadedMethod info FeatureT p) => OL.IsLabel t (FeatureT -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveFeatureTMethod t FeatureT, O.OverloadedMethod info FeatureT p, R.HasField t FeatureT p) => R.HasField t FeatureT p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveFeatureTMethod t FeatureT, O.OverloadedMethodInfo info FeatureT) => OL.IsLabel t (O.MethodProxy info FeatureT) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif