{-# LANGUAGE CPP, ForeignFunctionInterface #-} -- vim:filetype=haskell: -- -- XXX: Should we consider property names to be encoded in UTF-8 too -- (string values are already encoded to / decoded from UTF-8). {- | Legacy core functions from the C implementation. Before libxfconf can be use, it must be initialized by calling 'xfconfInit'. To free resources used by the library, call 'xfconfShutdown'. These calls are "recursive": multiple calls to 'xfconfInit' are allowed, but each call must be matched by a separate call to 'xfconfShutdown' to really free the library's resources. For more information, see: http:\/\/docs.xfce.org\/api\/xfconf\/xfconf-xfconf.html -} #include {# context lib="xfconf-0" prefix="xfconf" #} module System.XFCE.Xfconf.Unsafe ( xfconfInit, xfconfShutdown, ) where import System.Glib.GError (propagateGError) import System.XFCE.Xfconf.FFI {---------------------------------------------------------------------- -- Core ----------------------------------------------------------------------} foreign import ccall unsafe "xfconf_init" c_xfconf_init :: Ptr (Ptr ()) -> IO () -- | Initializes the Xfconf library. Can be called multiple times with -- no adverse effects. -- -- May throw a 'GError'. You can try to catch it with: -- -- @ -- catchGError xfconfInit -- (\(GError d c m) -> do print d;print c;print m) -- @ -- -- N.B.: most Haskell functions automatically calls xfconfInit when -- needed. You should NOT directly use this function. xfconfInit :: IO () xfconfInit = propagateGError (\errPtrPtr -> c_xfconf_init errPtrPtr) -- | Shuts down and frees any resources consumed by the Xfconf library. -- If 'xfconfInit' is called multiple times, 'xfconfShutdown' must be -- called an equal number of times to shut down the library. -- -- N.B.: most Haskell functions automatically calls xfconfShutdown when -- needed. You should NOT directly use this function. xfconfShutdown :: IO () xfconfShutdown = {#call unsafe xfconf_shutdown #}