{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.CharsetConverter.CharsetConverter' is an implementation of t'GI.Gio.Interfaces.Converter.Converter' based on
-- GIConv.

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

module GI.Gio.Objects.CharsetConverter
    ( 

-- * Exported types
    CharsetConverter(..)                    ,
    IsCharsetConverter                      ,
    toCharsetConverter                      ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveCharsetConverterMethod           ,
#endif


-- ** getNumFallbacks #method:getNumFallbacks#

#if defined(ENABLE_OVERLOADING)
    CharsetConverterGetNumFallbacksMethodInfo,
#endif
    charsetConverterGetNumFallbacks         ,


-- ** getUseFallback #method:getUseFallback#

#if defined(ENABLE_OVERLOADING)
    CharsetConverterGetUseFallbackMethodInfo,
#endif
    charsetConverterGetUseFallback          ,


-- ** new #method:new#

    charsetConverterNew                     ,


-- ** setUseFallback #method:setUseFallback#

#if defined(ENABLE_OVERLOADING)
    CharsetConverterSetUseFallbackMethodInfo,
#endif
    charsetConverterSetUseFallback          ,




 -- * Properties
-- ** fromCharset #attr:fromCharset#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    CharsetConverterFromCharsetPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
    charsetConverterFromCharset             ,
#endif
    constructCharsetConverterFromCharset    ,
    getCharsetConverterFromCharset          ,


-- ** toCharset #attr:toCharset#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    CharsetConverterToCharsetPropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    charsetConverterToCharset               ,
#endif
    constructCharsetConverterToCharset      ,
    getCharsetConverterToCharset            ,


-- ** useFallback #attr:useFallback#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    CharsetConverterUseFallbackPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
    charsetConverterUseFallback             ,
#endif
    constructCharsetConverterUseFallback    ,
    getCharsetConverterUseFallback          ,
    setCharsetConverterUseFallback          ,




    ) 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.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 GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Converter as Gio.Converter
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Initable as Gio.Initable

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

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

foreign import ccall "g_charset_converter_get_type"
    c_g_charset_converter_get_type :: IO B.Types.GType

instance B.Types.TypedObject CharsetConverter where
    glibType :: IO GType
glibType = IO GType
c_g_charset_converter_get_type

instance B.Types.GObject CharsetConverter

-- | Convert 'CharsetConverter' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue CharsetConverter where
    toGValue :: CharsetConverter -> IO GValue
toGValue CharsetConverter
o = do
        GType
gtype <- IO GType
c_g_charset_converter_get_type
        CharsetConverter
-> (Ptr CharsetConverter -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr CharsetConverter
o (GType
-> (GValue -> Ptr CharsetConverter -> IO ())
-> Ptr CharsetConverter
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr CharsetConverter -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO CharsetConverter
fromGValue GValue
gv = do
        Ptr CharsetConverter
ptr <- GValue -> IO (Ptr CharsetConverter)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr CharsetConverter)
        (ManagedPtr CharsetConverter -> CharsetConverter)
-> Ptr CharsetConverter -> IO CharsetConverter
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr CharsetConverter -> CharsetConverter
CharsetConverter Ptr CharsetConverter
ptr
        
    

-- | Type class for types which can be safely cast to `CharsetConverter`, for instance with `toCharsetConverter`.
class (SP.GObject o, O.IsDescendantOf CharsetConverter o) => IsCharsetConverter o
instance (SP.GObject o, O.IsDescendantOf CharsetConverter o) => IsCharsetConverter o

instance O.HasParentTypes CharsetConverter
type instance O.ParentTypes CharsetConverter = '[GObject.Object.Object, Gio.Converter.Converter, Gio.Initable.Initable]

-- | Cast to `CharsetConverter`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toCharsetConverter :: (MonadIO m, IsCharsetConverter o) => o -> m CharsetConverter
toCharsetConverter :: o -> m CharsetConverter
toCharsetConverter = IO CharsetConverter -> m CharsetConverter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CharsetConverter -> m CharsetConverter)
-> (o -> IO CharsetConverter) -> o -> m CharsetConverter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr CharsetConverter -> CharsetConverter)
-> o -> IO CharsetConverter
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr CharsetConverter -> CharsetConverter
CharsetConverter

#if defined(ENABLE_OVERLOADING)
type family ResolveCharsetConverterMethod (t :: Symbol) (o :: *) :: * where
    ResolveCharsetConverterMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveCharsetConverterMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveCharsetConverterMethod "convert" o = Gio.Converter.ConverterConvertMethodInfo
    ResolveCharsetConverterMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveCharsetConverterMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveCharsetConverterMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveCharsetConverterMethod "init" o = Gio.Initable.InitableInitMethodInfo
    ResolveCharsetConverterMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveCharsetConverterMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveCharsetConverterMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveCharsetConverterMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveCharsetConverterMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveCharsetConverterMethod "reset" o = Gio.Converter.ConverterResetMethodInfo
    ResolveCharsetConverterMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveCharsetConverterMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveCharsetConverterMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveCharsetConverterMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveCharsetConverterMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveCharsetConverterMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveCharsetConverterMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveCharsetConverterMethod "getNumFallbacks" o = CharsetConverterGetNumFallbacksMethodInfo
    ResolveCharsetConverterMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveCharsetConverterMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveCharsetConverterMethod "getUseFallback" o = CharsetConverterGetUseFallbackMethodInfo
    ResolveCharsetConverterMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveCharsetConverterMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveCharsetConverterMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveCharsetConverterMethod "setUseFallback" o = CharsetConverterSetUseFallbackMethodInfo
    ResolveCharsetConverterMethod l o = O.MethodResolutionFailed l o

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

#endif

-- VVV Prop "from-charset"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@from-charset@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' charsetConverter #fromCharset
-- @
getCharsetConverterFromCharset :: (MonadIO m, IsCharsetConverter o) => o -> m (Maybe T.Text)
getCharsetConverterFromCharset :: o -> m (Maybe Text)
getCharsetConverterFromCharset o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"from-charset"

-- | Construct a `GValueConstruct` with valid value for the “@from-charset@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCharsetConverterFromCharset :: (IsCharsetConverter o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructCharsetConverterFromCharset :: Text -> m (GValueConstruct o)
constructCharsetConverterFromCharset Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"from-charset" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data CharsetConverterFromCharsetPropertyInfo
instance AttrInfo CharsetConverterFromCharsetPropertyInfo where
    type AttrAllowedOps CharsetConverterFromCharsetPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CharsetConverterFromCharsetPropertyInfo = IsCharsetConverter
    type AttrSetTypeConstraint CharsetConverterFromCharsetPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint CharsetConverterFromCharsetPropertyInfo = (~) T.Text
    type AttrTransferType CharsetConverterFromCharsetPropertyInfo = T.Text
    type AttrGetType CharsetConverterFromCharsetPropertyInfo = (Maybe T.Text)
    type AttrLabel CharsetConverterFromCharsetPropertyInfo = "from-charset"
    type AttrOrigin CharsetConverterFromCharsetPropertyInfo = CharsetConverter
    attrGet = getCharsetConverterFromCharset
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructCharsetConverterFromCharset
    attrClear = undefined
#endif

-- VVV Prop "to-charset"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@to-charset@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' charsetConverter #toCharset
-- @
getCharsetConverterToCharset :: (MonadIO m, IsCharsetConverter o) => o -> m (Maybe T.Text)
getCharsetConverterToCharset :: o -> m (Maybe Text)
getCharsetConverterToCharset o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"to-charset"

-- | Construct a `GValueConstruct` with valid value for the “@to-charset@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCharsetConverterToCharset :: (IsCharsetConverter o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructCharsetConverterToCharset :: Text -> m (GValueConstruct o)
constructCharsetConverterToCharset Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"to-charset" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data CharsetConverterToCharsetPropertyInfo
instance AttrInfo CharsetConverterToCharsetPropertyInfo where
    type AttrAllowedOps CharsetConverterToCharsetPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CharsetConverterToCharsetPropertyInfo = IsCharsetConverter
    type AttrSetTypeConstraint CharsetConverterToCharsetPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint CharsetConverterToCharsetPropertyInfo = (~) T.Text
    type AttrTransferType CharsetConverterToCharsetPropertyInfo = T.Text
    type AttrGetType CharsetConverterToCharsetPropertyInfo = (Maybe T.Text)
    type AttrLabel CharsetConverterToCharsetPropertyInfo = "to-charset"
    type AttrOrigin CharsetConverterToCharsetPropertyInfo = CharsetConverter
    attrGet = getCharsetConverterToCharset
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructCharsetConverterToCharset
    attrClear = undefined
#endif

-- VVV Prop "use-fallback"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@use-fallback@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' charsetConverter #useFallback
-- @
getCharsetConverterUseFallback :: (MonadIO m, IsCharsetConverter o) => o -> m Bool
getCharsetConverterUseFallback :: o -> m Bool
getCharsetConverterUseFallback o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"use-fallback"

-- | Set the value of the “@use-fallback@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' charsetConverter [ #useFallback 'Data.GI.Base.Attributes.:=' value ]
-- @
setCharsetConverterUseFallback :: (MonadIO m, IsCharsetConverter o) => o -> Bool -> m ()
setCharsetConverterUseFallback :: o -> Bool -> m ()
setCharsetConverterUseFallback o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"use-fallback" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@use-fallback@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCharsetConverterUseFallback :: (IsCharsetConverter o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructCharsetConverterUseFallback :: Bool -> m (GValueConstruct o)
constructCharsetConverterUseFallback Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"use-fallback" Bool
val

#if defined(ENABLE_OVERLOADING)
data CharsetConverterUseFallbackPropertyInfo
instance AttrInfo CharsetConverterUseFallbackPropertyInfo where
    type AttrAllowedOps CharsetConverterUseFallbackPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint CharsetConverterUseFallbackPropertyInfo = IsCharsetConverter
    type AttrSetTypeConstraint CharsetConverterUseFallbackPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint CharsetConverterUseFallbackPropertyInfo = (~) Bool
    type AttrTransferType CharsetConverterUseFallbackPropertyInfo = Bool
    type AttrGetType CharsetConverterUseFallbackPropertyInfo = Bool
    type AttrLabel CharsetConverterUseFallbackPropertyInfo = "use-fallback"
    type AttrOrigin CharsetConverterUseFallbackPropertyInfo = CharsetConverter
    attrGet = getCharsetConverterUseFallback
    attrSet = setCharsetConverterUseFallback
    attrTransfer _ v = do
        return v
    attrConstruct = constructCharsetConverterUseFallback
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList CharsetConverter
type instance O.AttributeList CharsetConverter = CharsetConverterAttributeList
type CharsetConverterAttributeList = ('[ '("fromCharset", CharsetConverterFromCharsetPropertyInfo), '("toCharset", CharsetConverterToCharsetPropertyInfo), '("useFallback", CharsetConverterUseFallbackPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
charsetConverterFromCharset :: AttrLabelProxy "fromCharset"
charsetConverterFromCharset = AttrLabelProxy

charsetConverterToCharset :: AttrLabelProxy "toCharset"
charsetConverterToCharset = AttrLabelProxy

charsetConverterUseFallback :: AttrLabelProxy "useFallback"
charsetConverterUseFallback = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList CharsetConverter = CharsetConverterSignalList
type CharsetConverterSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method CharsetConverter::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "to_charset"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "destination charset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "from_charset"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "source charset" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "CharsetConverter" })
-- throws : True
-- Skip return : False

foreign import ccall "g_charset_converter_new" g_charset_converter_new :: 
    CString ->                              -- to_charset : TBasicType TUTF8
    CString ->                              -- from_charset : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr CharsetConverter)

-- | Creates a new t'GI.Gio.Objects.CharsetConverter.CharsetConverter'.
-- 
-- /Since: 2.24/
charsetConverterNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@toCharset@/: destination charset
    -> T.Text
    -- ^ /@fromCharset@/: source charset
    -> m CharsetConverter
    -- ^ __Returns:__ a new t'GI.Gio.Objects.CharsetConverter.CharsetConverter' or 'P.Nothing' on error. /(Can throw 'Data.GI.Base.GError.GError')/
charsetConverterNew :: Text -> Text -> m CharsetConverter
charsetConverterNew Text
toCharset Text
fromCharset = IO CharsetConverter -> m CharsetConverter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CharsetConverter -> m CharsetConverter)
-> IO CharsetConverter -> m CharsetConverter
forall a b. (a -> b) -> a -> b
$ do
    CString
toCharset' <- Text -> IO CString
textToCString Text
toCharset
    CString
fromCharset' <- Text -> IO CString
textToCString Text
fromCharset
    IO CharsetConverter -> IO () -> IO CharsetConverter
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr CharsetConverter
result <- (Ptr (Ptr GError) -> IO (Ptr CharsetConverter))
-> IO (Ptr CharsetConverter)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr CharsetConverter))
 -> IO (Ptr CharsetConverter))
-> (Ptr (Ptr GError) -> IO (Ptr CharsetConverter))
-> IO (Ptr CharsetConverter)
forall a b. (a -> b) -> a -> b
$ CString -> CString -> Ptr (Ptr GError) -> IO (Ptr CharsetConverter)
g_charset_converter_new CString
toCharset' CString
fromCharset'
        Text -> Ptr CharsetConverter -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"charsetConverterNew" Ptr CharsetConverter
result
        CharsetConverter
result' <- ((ManagedPtr CharsetConverter -> CharsetConverter)
-> Ptr CharsetConverter -> IO CharsetConverter
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr CharsetConverter -> CharsetConverter
CharsetConverter) Ptr CharsetConverter
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
toCharset'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fromCharset'
        CharsetConverter -> IO CharsetConverter
forall (m :: * -> *) a. Monad m => a -> m a
return CharsetConverter
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
toCharset'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fromCharset'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method CharsetConverter::get_num_fallbacks
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "converter"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "CharsetConverter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCharsetConverter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_charset_converter_get_num_fallbacks" g_charset_converter_get_num_fallbacks :: 
    Ptr CharsetConverter ->                 -- converter : TInterface (Name {namespace = "Gio", name = "CharsetConverter"})
    IO Word32

-- | Gets the number of fallbacks that /@converter@/ has applied so far.
-- 
-- /Since: 2.24/
charsetConverterGetNumFallbacks ::
    (B.CallStack.HasCallStack, MonadIO m, IsCharsetConverter a) =>
    a
    -- ^ /@converter@/: a t'GI.Gio.Objects.CharsetConverter.CharsetConverter'
    -> m Word32
    -- ^ __Returns:__ the number of fallbacks that /@converter@/ has applied
charsetConverterGetNumFallbacks :: a -> m Word32
charsetConverterGetNumFallbacks a
converter = 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
$ do
    Ptr CharsetConverter
converter' <- a -> IO (Ptr CharsetConverter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
converter
    Word32
result <- Ptr CharsetConverter -> IO Word32
g_charset_converter_get_num_fallbacks Ptr CharsetConverter
converter'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
converter
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data CharsetConverterGetNumFallbacksMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsCharsetConverter a) => O.MethodInfo CharsetConverterGetNumFallbacksMethodInfo a signature where
    overloadedMethod = charsetConverterGetNumFallbacks

#endif

-- method CharsetConverter::get_use_fallback
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "converter"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "CharsetConverter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCharsetConverter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_charset_converter_get_use_fallback" g_charset_converter_get_use_fallback :: 
    Ptr CharsetConverter ->                 -- converter : TInterface (Name {namespace = "Gio", name = "CharsetConverter"})
    IO CInt

-- | Gets the t'GI.Gio.Objects.CharsetConverter.CharsetConverter':@/use-fallback/@ property.
-- 
-- /Since: 2.24/
charsetConverterGetUseFallback ::
    (B.CallStack.HasCallStack, MonadIO m, IsCharsetConverter a) =>
    a
    -- ^ /@converter@/: a t'GI.Gio.Objects.CharsetConverter.CharsetConverter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if fallbacks are used by /@converter@/
charsetConverterGetUseFallback :: a -> m Bool
charsetConverterGetUseFallback a
converter = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr CharsetConverter
converter' <- a -> IO (Ptr CharsetConverter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
converter
    CInt
result <- Ptr CharsetConverter -> IO CInt
g_charset_converter_get_use_fallback Ptr CharsetConverter
converter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
converter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data CharsetConverterGetUseFallbackMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsCharsetConverter a) => O.MethodInfo CharsetConverterGetUseFallbackMethodInfo a signature where
    overloadedMethod = charsetConverterGetUseFallback

#endif

-- method CharsetConverter::set_use_fallback
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "converter"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "CharsetConverter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCharsetConverter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "use_fallback"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to use fallbacks"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_charset_converter_set_use_fallback" g_charset_converter_set_use_fallback :: 
    Ptr CharsetConverter ->                 -- converter : TInterface (Name {namespace = "Gio", name = "CharsetConverter"})
    CInt ->                                 -- use_fallback : TBasicType TBoolean
    IO ()

-- | Sets the t'GI.Gio.Objects.CharsetConverter.CharsetConverter':@/use-fallback/@ property.
-- 
-- /Since: 2.24/
charsetConverterSetUseFallback ::
    (B.CallStack.HasCallStack, MonadIO m, IsCharsetConverter a) =>
    a
    -- ^ /@converter@/: a t'GI.Gio.Objects.CharsetConverter.CharsetConverter'
    -> Bool
    -- ^ /@useFallback@/: 'P.True' to use fallbacks
    -> m ()
charsetConverterSetUseFallback :: a -> Bool -> m ()
charsetConverterSetUseFallback a
converter Bool
useFallback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CharsetConverter
converter' <- a -> IO (Ptr CharsetConverter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
converter
    let useFallback' :: CInt
useFallback' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
useFallback
    Ptr CharsetConverter -> CInt -> IO ()
g_charset_converter_set_use_fallback Ptr CharsetConverter
converter' CInt
useFallback'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
converter
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CharsetConverterSetUseFallbackMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsCharsetConverter a) => O.MethodInfo CharsetConverterSetUseFallbackMethodInfo a signature where
    overloadedMethod = charsetConverterSetUseFallback

#endif