Copyright | Will Thompson Iñaki García Etxebarria and Jonas Platte |
---|---|
License | LGPL-2.1 |
Maintainer | Iñaki García Etxebarria |
Safe Haskell | None |
Language | Haskell2010 |
A union holding the value of the token.
Synopsis
- newtype TokenValue = TokenValue (ManagedPtr TokenValue)
- newZeroTokenValue :: MonadIO m => m TokenValue
- getTokenValueVBinary :: MonadIO m => TokenValue -> m CULong
- setTokenValueVBinary :: MonadIO m => TokenValue -> CULong -> m ()
- getTokenValueVChar :: MonadIO m => TokenValue -> m Word8
- setTokenValueVChar :: MonadIO m => TokenValue -> Word8 -> m ()
- clearTokenValueVComment :: MonadIO m => TokenValue -> m ()
- getTokenValueVComment :: MonadIO m => TokenValue -> m (Maybe Text)
- setTokenValueVComment :: MonadIO m => TokenValue -> CString -> m ()
- getTokenValueVError :: MonadIO m => TokenValue -> m Word32
- setTokenValueVError :: MonadIO m => TokenValue -> Word32 -> m ()
- getTokenValueVFloat :: MonadIO m => TokenValue -> m Double
- setTokenValueVFloat :: MonadIO m => TokenValue -> Double -> m ()
- getTokenValueVHex :: MonadIO m => TokenValue -> m CULong
- setTokenValueVHex :: MonadIO m => TokenValue -> CULong -> m ()
- clearTokenValueVIdentifier :: MonadIO m => TokenValue -> m ()
- getTokenValueVIdentifier :: MonadIO m => TokenValue -> m (Maybe Text)
- setTokenValueVIdentifier :: MonadIO m => TokenValue -> CString -> m ()
- getTokenValueVInt :: MonadIO m => TokenValue -> m CULong
- setTokenValueVInt :: MonadIO m => TokenValue -> CULong -> m ()
- getTokenValueVInt64 :: MonadIO m => TokenValue -> m Word64
- setTokenValueVInt64 :: MonadIO m => TokenValue -> Word64 -> m ()
- getTokenValueVOctal :: MonadIO m => TokenValue -> m CULong
- setTokenValueVOctal :: MonadIO m => TokenValue -> CULong -> m ()
- clearTokenValueVString :: MonadIO m => TokenValue -> m ()
- getTokenValueVString :: MonadIO m => TokenValue -> m (Maybe Text)
- setTokenValueVString :: MonadIO m => TokenValue -> CString -> m ()
- clearTokenValueVSymbol :: MonadIO m => TokenValue -> m ()
- getTokenValueVSymbol :: MonadIO m => TokenValue -> m (Ptr ())
- setTokenValueVSymbol :: MonadIO m => TokenValue -> Ptr () -> m ()
Exported types
newtype TokenValue Source #
Memory-managed wrapper type.
Instances
Eq TokenValue Source # | |
Defined in GI.GLib.Unions.TokenValue (==) :: TokenValue -> TokenValue -> Bool # (/=) :: TokenValue -> TokenValue -> Bool # | |
ManagedPtrNewtype TokenValue Source # | |
Defined in GI.GLib.Unions.TokenValue | |
BoxedPtr TokenValue Source # | |
Defined in GI.GLib.Unions.TokenValue boxedPtrCopy :: TokenValue -> IO TokenValue # boxedPtrFree :: TokenValue -> IO () # | |
CallocPtr TokenValue Source # | |
Defined in GI.GLib.Unions.TokenValue boxedPtrCalloc :: IO (Ptr TokenValue) # | |
tag ~ 'AttrSet => Constructible TokenValue tag Source # | |
Defined in GI.GLib.Unions.TokenValue new :: MonadIO m => (ManagedPtr TokenValue -> TokenValue) -> [AttrOp TokenValue tag] -> m TokenValue # |
newZeroTokenValue :: MonadIO m => m TokenValue Source #
Construct a TokenValue
struct initialized to zero.
Methods
Overloaded methods
Properties
vBinary
token binary integer value
getTokenValueVBinary :: MonadIO m => TokenValue -> m CULong Source #
Get the value of the “v_binary
” field.
When overloading is enabled, this is equivalent to
get
tokenValue #vBinary
setTokenValueVBinary :: MonadIO m => TokenValue -> CULong -> m () Source #
Set the value of the “v_binary
” field.
When overloading is enabled, this is equivalent to
set
tokenValue [ #vBinary:=
value ]
vChar
character value
getTokenValueVChar :: MonadIO m => TokenValue -> m Word8 Source #
Get the value of the “v_char
” field.
When overloading is enabled, this is equivalent to
get
tokenValue #vChar
setTokenValueVChar :: MonadIO m => TokenValue -> Word8 -> m () Source #
Set the value of the “v_char
” field.
When overloading is enabled, this is equivalent to
set
tokenValue [ #vChar:=
value ]
vComment
comment value
clearTokenValueVComment :: MonadIO m => TokenValue -> m () Source #
Set the value of the “v_comment
” field to Nothing
.
When overloading is enabled, this is equivalent to
clear
#vComment
getTokenValueVComment :: MonadIO m => TokenValue -> m (Maybe Text) Source #
Get the value of the “v_comment
” field.
When overloading is enabled, this is equivalent to
get
tokenValue #vComment
setTokenValueVComment :: MonadIO m => TokenValue -> CString -> m () Source #
Set the value of the “v_comment
” field.
When overloading is enabled, this is equivalent to
set
tokenValue [ #vComment:=
value ]
vError
error value
getTokenValueVError :: MonadIO m => TokenValue -> m Word32 Source #
Get the value of the “v_error
” field.
When overloading is enabled, this is equivalent to
get
tokenValue #vError
setTokenValueVError :: MonadIO m => TokenValue -> Word32 -> m () Source #
Set the value of the “v_error
” field.
When overloading is enabled, this is equivalent to
set
tokenValue [ #vError:=
value ]
vFloat
floating point value
getTokenValueVFloat :: MonadIO m => TokenValue -> m Double Source #
Get the value of the “v_float
” field.
When overloading is enabled, this is equivalent to
get
tokenValue #vFloat
setTokenValueVFloat :: MonadIO m => TokenValue -> Double -> m () Source #
Set the value of the “v_float
” field.
When overloading is enabled, this is equivalent to
set
tokenValue [ #vFloat:=
value ]
vHex
hex integer value
getTokenValueVHex :: MonadIO m => TokenValue -> m CULong Source #
Get the value of the “v_hex
” field.
When overloading is enabled, this is equivalent to
get
tokenValue #vHex
setTokenValueVHex :: MonadIO m => TokenValue -> CULong -> m () Source #
Set the value of the “v_hex
” field.
When overloading is enabled, this is equivalent to
set
tokenValue [ #vHex:=
value ]
vIdentifier
token identifier value
clearTokenValueVIdentifier :: MonadIO m => TokenValue -> m () Source #
Set the value of the “v_identifier
” field to Nothing
.
When overloading is enabled, this is equivalent to
clear
#vIdentifier
getTokenValueVIdentifier :: MonadIO m => TokenValue -> m (Maybe Text) Source #
Get the value of the “v_identifier
” field.
When overloading is enabled, this is equivalent to
get
tokenValue #vIdentifier
setTokenValueVIdentifier :: MonadIO m => TokenValue -> CString -> m () Source #
Set the value of the “v_identifier
” field.
When overloading is enabled, this is equivalent to
set
tokenValue [ #vIdentifier:=
value ]
vInt
integer value
getTokenValueVInt :: MonadIO m => TokenValue -> m CULong Source #
Get the value of the “v_int
” field.
When overloading is enabled, this is equivalent to
get
tokenValue #vInt
setTokenValueVInt :: MonadIO m => TokenValue -> CULong -> m () Source #
Set the value of the “v_int
” field.
When overloading is enabled, this is equivalent to
set
tokenValue [ #vInt:=
value ]
vInt64
64-bit integer value
getTokenValueVInt64 :: MonadIO m => TokenValue -> m Word64 Source #
Get the value of the “v_int64
” field.
When overloading is enabled, this is equivalent to
get
tokenValue #vInt64
setTokenValueVInt64 :: MonadIO m => TokenValue -> Word64 -> m () Source #
Set the value of the “v_int64
” field.
When overloading is enabled, this is equivalent to
set
tokenValue [ #vInt64:=
value ]
vOctal
octal integer value
getTokenValueVOctal :: MonadIO m => TokenValue -> m CULong Source #
Get the value of the “v_octal
” field.
When overloading is enabled, this is equivalent to
get
tokenValue #vOctal
setTokenValueVOctal :: MonadIO m => TokenValue -> CULong -> m () Source #
Set the value of the “v_octal
” field.
When overloading is enabled, this is equivalent to
set
tokenValue [ #vOctal:=
value ]
vString
string value
clearTokenValueVString :: MonadIO m => TokenValue -> m () Source #
Set the value of the “v_string
” field to Nothing
.
When overloading is enabled, this is equivalent to
clear
#vString
getTokenValueVString :: MonadIO m => TokenValue -> m (Maybe Text) Source #
Get the value of the “v_string
” field.
When overloading is enabled, this is equivalent to
get
tokenValue #vString
setTokenValueVString :: MonadIO m => TokenValue -> CString -> m () Source #
Set the value of the “v_string
” field.
When overloading is enabled, this is equivalent to
set
tokenValue [ #vString:=
value ]
vSymbol
token symbol value
clearTokenValueVSymbol :: MonadIO m => TokenValue -> m () Source #
Set the value of the “v_symbol
” field to Nothing
.
When overloading is enabled, this is equivalent to
clear
#vSymbol
getTokenValueVSymbol :: MonadIO m => TokenValue -> m (Ptr ()) Source #
Get the value of the “v_symbol
” field.
When overloading is enabled, this is equivalent to
get
tokenValue #vSymbol
setTokenValueVSymbol :: MonadIO m => TokenValue -> Ptr () -> m () Source #
Set the value of the “v_symbol
” field.
When overloading is enabled, this is equivalent to
set
tokenValue [ #vSymbol:=
value ]