{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Represents a day between January 1, Year 1 and a few thousand years in
-- the future. None of its members should be accessed directly.
-- 
-- If the @GDate@ is obtained from 'GI.GLib.Structs.Date.dateNew', it will be safe
-- to mutate but invalid and thus not safe for calendrical computations.
-- 
-- If it\'s declared on the stack, it will contain garbage so must be
-- initialized with 'GI.GLib.Structs.Date.dateClear'. 'GI.GLib.Structs.Date.dateClear' makes the date invalid
-- but safe. An invalid date doesn\'t represent a day, it\'s \"empty.\" A date
-- becomes valid after you set it to a Julian day or you set a day, month,
-- and year.

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

module GI.GLib.Structs.Date
    ( 

-- * Exported types
    Date(..)                                ,
    newZeroDate                             ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addDays]("GI.GLib.Structs.Date#g:method:addDays"), [addMonths]("GI.GLib.Structs.Date#g:method:addMonths"), [addYears]("GI.GLib.Structs.Date#g:method:addYears"), [clamp]("GI.GLib.Structs.Date#g:method:clamp"), [clear]("GI.GLib.Structs.Date#g:method:clear"), [compare]("GI.GLib.Structs.Date#g:method:compare"), [copy]("GI.GLib.Structs.Date#g:method:copy"), [daysBetween]("GI.GLib.Structs.Date#g:method:daysBetween"), [free]("GI.GLib.Structs.Date#g:method:free"), [isFirstOfMonth]("GI.GLib.Structs.Date#g:method:isFirstOfMonth"), [isLastOfMonth]("GI.GLib.Structs.Date#g:method:isLastOfMonth"), [order]("GI.GLib.Structs.Date#g:method:order"), [subtractDays]("GI.GLib.Structs.Date#g:method:subtractDays"), [subtractMonths]("GI.GLib.Structs.Date#g:method:subtractMonths"), [subtractYears]("GI.GLib.Structs.Date#g:method:subtractYears"), [toStructTm]("GI.GLib.Structs.Date#g:method:toStructTm"), [valid]("GI.GLib.Structs.Date#g:method:valid").
-- 
-- ==== Getters
-- [getDay]("GI.GLib.Structs.Date#g:method:getDay"), [getDayOfYear]("GI.GLib.Structs.Date#g:method:getDayOfYear"), [getIso8601WeekOfYear]("GI.GLib.Structs.Date#g:method:getIso8601WeekOfYear"), [getJulian]("GI.GLib.Structs.Date#g:method:getJulian"), [getMondayWeekOfYear]("GI.GLib.Structs.Date#g:method:getMondayWeekOfYear"), [getMonth]("GI.GLib.Structs.Date#g:method:getMonth"), [getSundayWeekOfYear]("GI.GLib.Structs.Date#g:method:getSundayWeekOfYear"), [getWeekday]("GI.GLib.Structs.Date#g:method:getWeekday"), [getYear]("GI.GLib.Structs.Date#g:method:getYear").
-- 
-- ==== Setters
-- [setDay]("GI.GLib.Structs.Date#g:method:setDay"), [setDmy]("GI.GLib.Structs.Date#g:method:setDmy"), [setJulian]("GI.GLib.Structs.Date#g:method:setJulian"), [setMonth]("GI.GLib.Structs.Date#g:method:setMonth"), [setParse]("GI.GLib.Structs.Date#g:method:setParse"), [setTime]("GI.GLib.Structs.Date#g:method:setTime"), [setTimeT]("GI.GLib.Structs.Date#g:method:setTimeT"), [setTimeVal]("GI.GLib.Structs.Date#g:method:setTimeVal"), [setYear]("GI.GLib.Structs.Date#g:method:setYear").

#if defined(ENABLE_OVERLOADING)
    ResolveDateMethod                       ,
#endif

-- ** addDays #method:addDays#

#if defined(ENABLE_OVERLOADING)
    DateAddDaysMethodInfo                   ,
#endif
    dateAddDays                             ,


-- ** addMonths #method:addMonths#

#if defined(ENABLE_OVERLOADING)
    DateAddMonthsMethodInfo                 ,
#endif
    dateAddMonths                           ,


-- ** addYears #method:addYears#

#if defined(ENABLE_OVERLOADING)
    DateAddYearsMethodInfo                  ,
#endif
    dateAddYears                            ,


-- ** clamp #method:clamp#

#if defined(ENABLE_OVERLOADING)
    DateClampMethodInfo                     ,
#endif
    dateClamp                               ,


-- ** clear #method:clear#

#if defined(ENABLE_OVERLOADING)
    DateClearMethodInfo                     ,
#endif
    dateClear                               ,


-- ** compare #method:compare#

#if defined(ENABLE_OVERLOADING)
    DateCompareMethodInfo                   ,
#endif
    dateCompare                             ,


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    DateCopyMethodInfo                      ,
#endif
    dateCopy                                ,


-- ** daysBetween #method:daysBetween#

#if defined(ENABLE_OVERLOADING)
    DateDaysBetweenMethodInfo               ,
#endif
    dateDaysBetween                         ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    DateFreeMethodInfo                      ,
#endif
    dateFree                                ,


-- ** getDay #method:getDay#

#if defined(ENABLE_OVERLOADING)
    DateGetDayMethodInfo                    ,
#endif
    dateGetDay                              ,


-- ** getDayOfYear #method:getDayOfYear#

#if defined(ENABLE_OVERLOADING)
    DateGetDayOfYearMethodInfo              ,
#endif
    dateGetDayOfYear                        ,


-- ** getDaysInMonth #method:getDaysInMonth#

    dateGetDaysInMonth                      ,


-- ** getIso8601WeekOfYear #method:getIso8601WeekOfYear#

#if defined(ENABLE_OVERLOADING)
    DateGetIso8601WeekOfYearMethodInfo      ,
#endif
    dateGetIso8601WeekOfYear                ,


-- ** getJulian #method:getJulian#

#if defined(ENABLE_OVERLOADING)
    DateGetJulianMethodInfo                 ,
#endif
    dateGetJulian                           ,


-- ** getMondayWeekOfYear #method:getMondayWeekOfYear#

#if defined(ENABLE_OVERLOADING)
    DateGetMondayWeekOfYearMethodInfo       ,
#endif
    dateGetMondayWeekOfYear                 ,


-- ** getMondayWeeksInYear #method:getMondayWeeksInYear#

    dateGetMondayWeeksInYear                ,


-- ** getMonth #method:getMonth#

#if defined(ENABLE_OVERLOADING)
    DateGetMonthMethodInfo                  ,
#endif
    dateGetMonth                            ,


-- ** getSundayWeekOfYear #method:getSundayWeekOfYear#

#if defined(ENABLE_OVERLOADING)
    DateGetSundayWeekOfYearMethodInfo       ,
#endif
    dateGetSundayWeekOfYear                 ,


-- ** getSundayWeeksInYear #method:getSundayWeeksInYear#

    dateGetSundayWeeksInYear                ,


-- ** getWeekday #method:getWeekday#

#if defined(ENABLE_OVERLOADING)
    DateGetWeekdayMethodInfo                ,
#endif
    dateGetWeekday                          ,


-- ** getYear #method:getYear#

#if defined(ENABLE_OVERLOADING)
    DateGetYearMethodInfo                   ,
#endif
    dateGetYear                             ,


-- ** isFirstOfMonth #method:isFirstOfMonth#

#if defined(ENABLE_OVERLOADING)
    DateIsFirstOfMonthMethodInfo            ,
#endif
    dateIsFirstOfMonth                      ,


-- ** isLastOfMonth #method:isLastOfMonth#

#if defined(ENABLE_OVERLOADING)
    DateIsLastOfMonthMethodInfo             ,
#endif
    dateIsLastOfMonth                       ,


-- ** isLeapYear #method:isLeapYear#

    dateIsLeapYear                          ,


-- ** new #method:new#

    dateNew                                 ,


-- ** newDmy #method:newDmy#

    dateNewDmy                              ,


-- ** newJulian #method:newJulian#

    dateNewJulian                           ,


-- ** order #method:order#

#if defined(ENABLE_OVERLOADING)
    DateOrderMethodInfo                     ,
#endif
    dateOrder                               ,


-- ** setDay #method:setDay#

#if defined(ENABLE_OVERLOADING)
    DateSetDayMethodInfo                    ,
#endif
    dateSetDay                              ,


-- ** setDmy #method:setDmy#

#if defined(ENABLE_OVERLOADING)
    DateSetDmyMethodInfo                    ,
#endif
    dateSetDmy                              ,


-- ** setJulian #method:setJulian#

#if defined(ENABLE_OVERLOADING)
    DateSetJulianMethodInfo                 ,
#endif
    dateSetJulian                           ,


-- ** setMonth #method:setMonth#

#if defined(ENABLE_OVERLOADING)
    DateSetMonthMethodInfo                  ,
#endif
    dateSetMonth                            ,


-- ** setParse #method:setParse#

#if defined(ENABLE_OVERLOADING)
    DateSetParseMethodInfo                  ,
#endif
    dateSetParse                            ,


-- ** setTime #method:setTime#

#if defined(ENABLE_OVERLOADING)
    DateSetTimeMethodInfo                   ,
#endif
    dateSetTime                             ,


-- ** setTimeT #method:setTimeT#

#if defined(ENABLE_OVERLOADING)
    DateSetTimeTMethodInfo                  ,
#endif
    dateSetTimeT                            ,


-- ** setTimeVal #method:setTimeVal#

#if defined(ENABLE_OVERLOADING)
    DateSetTimeValMethodInfo                ,
#endif
    dateSetTimeVal                          ,


-- ** setYear #method:setYear#

#if defined(ENABLE_OVERLOADING)
    DateSetYearMethodInfo                   ,
#endif
    dateSetYear                             ,


-- ** strftime #method:strftime#

    dateStrftime                            ,


-- ** subtractDays #method:subtractDays#

#if defined(ENABLE_OVERLOADING)
    DateSubtractDaysMethodInfo              ,
#endif
    dateSubtractDays                        ,


-- ** subtractMonths #method:subtractMonths#

#if defined(ENABLE_OVERLOADING)
    DateSubtractMonthsMethodInfo            ,
#endif
    dateSubtractMonths                      ,


-- ** subtractYears #method:subtractYears#

#if defined(ENABLE_OVERLOADING)
    DateSubtractYearsMethodInfo             ,
#endif
    dateSubtractYears                       ,


-- ** toStructTm #method:toStructTm#

#if defined(ENABLE_OVERLOADING)
    DateToStructTmMethodInfo                ,
#endif
    dateToStructTm                          ,


-- ** valid #method:valid#

#if defined(ENABLE_OVERLOADING)
    DateValidMethodInfo                     ,
#endif
    dateValid                               ,


-- ** validDay #method:validDay#

    dateValidDay                            ,


-- ** validDmy #method:validDmy#

    dateValidDmy                            ,


-- ** validJulian #method:validJulian#

    dateValidJulian                         ,


-- ** validMonth #method:validMonth#

    dateValidMonth                          ,


-- ** validWeekday #method:validWeekday#

    dateValidWeekday                        ,


-- ** validYear #method:validYear#

    dateValidYear                           ,




 -- * Properties


-- ** day #attr:day#
-- | the day of the day-month-year representation of the date,
--   as a number between 1 and 31

#if defined(ENABLE_OVERLOADING)
    date_day                                ,
#endif
    getDateDay                              ,
    setDateDay                              ,


-- ** dmy #attr:dmy#
-- | this is set if /@day@/, /@month@/ and /@year@/ are valid

#if defined(ENABLE_OVERLOADING)
    date_dmy                                ,
#endif
    getDateDmy                              ,
    setDateDmy                              ,


-- ** julian #attr:julian#
-- | this bit is set if /@julianDays@/ is valid

#if defined(ENABLE_OVERLOADING)
    date_julian                             ,
#endif
    getDateJulian                           ,
    setDateJulian                           ,


-- ** julianDays #attr:julianDays#
-- | the Julian representation of the date

#if defined(ENABLE_OVERLOADING)
    date_julianDays                         ,
#endif
    getDateJulianDays                       ,
    setDateJulianDays                       ,


-- ** month #attr:month#
-- | the day of the day-month-year representation of the date,
--   as a number between 1 and 12

#if defined(ENABLE_OVERLOADING)
    date_month                              ,
#endif
    getDateMonth                            ,
    setDateMonth                            ,


-- ** year #attr:year#
-- | the day of the day-month-year representation of the date

#if defined(ENABLE_OVERLOADING)
    date_year                               ,
#endif
    getDateYear                             ,
    setDateYear                             ,




    ) 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.Coerce as Coerce
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

import {-# SOURCE #-} qualified GI.GLib.Enums as GLib.Enums
import {-# SOURCE #-} qualified GI.GLib.Structs.TimeVal as GLib.TimeVal

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

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

foreign import ccall "g_date_get_type" c_g_date_get_type :: 
    IO GType

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

instance B.Types.TypedObject Date where
    glibType :: IO GType
glibType = IO GType
c_g_date_get_type

instance B.Types.GBoxed Date

-- | Convert 'Date' 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 Date) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_date_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Date -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Date
P.Nothing = Ptr GValue -> Ptr Date -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Date
forall a. Ptr a
FP.nullPtr :: FP.Ptr Date)
    gvalueSet_ Ptr GValue
gv (P.Just Date
obj) = Date -> (Ptr Date -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Date
obj (Ptr GValue -> Ptr Date -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Date)
gvalueGet_ Ptr GValue
gv = do
        Ptr Date
ptr <- Ptr GValue -> IO (Ptr Date)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Date)
        if Ptr Date
ptr Ptr Date -> Ptr Date -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Date
forall a. Ptr a
FP.nullPtr
        then Date -> Maybe Date
forall a. a -> Maybe a
P.Just (Date -> Maybe Date) -> IO Date -> IO (Maybe Date)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Date -> Date) -> Ptr Date -> IO Date
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Date -> Date
Date Ptr Date
ptr
        else Maybe Date -> IO (Maybe Date)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Date
forall a. Maybe a
P.Nothing
        
    

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

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


-- | Get the value of the “@julian_days@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' date #julianDays
-- @
getDateJulianDays :: MonadIO m => Date -> m Word32
getDateJulianDays :: forall (m :: * -> *). MonadIO m => Date -> m Word32
getDateJulianDays Date
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
$ Date -> (Ptr Date -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Date
s ((Ptr Date -> IO Word32) -> IO Word32)
-> (Ptr Date -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr Date
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr Date
ptr Ptr Date -> 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 “@julian_days@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' date [ #julianDays 'Data.GI.Base.Attributes.:=' value ]
-- @
setDateJulianDays :: MonadIO m => Date -> Word32 -> m ()
setDateJulianDays :: forall (m :: * -> *). MonadIO m => Date -> Word32 -> m ()
setDateJulianDays Date
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
$ Date -> (Ptr Date -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Date
s ((Ptr Date -> IO ()) -> IO ()) -> (Ptr Date -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Date
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Date
ptr Ptr Date -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data DateJulianDaysFieldInfo
instance AttrInfo DateJulianDaysFieldInfo where
    type AttrBaseTypeConstraint DateJulianDaysFieldInfo = (~) Date
    type AttrAllowedOps DateJulianDaysFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DateJulianDaysFieldInfo = (~) Word32
    type AttrTransferTypeConstraint DateJulianDaysFieldInfo = (~)Word32
    type AttrTransferType DateJulianDaysFieldInfo = Word32
    type AttrGetType DateJulianDaysFieldInfo = Word32
    type AttrLabel DateJulianDaysFieldInfo = "julian_days"
    type AttrOrigin DateJulianDaysFieldInfo = Date
    attrGet = getDateJulianDays
    attrSet = setDateJulianDays
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.julianDays"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#g:attr:julianDays"
        })

date_julianDays :: AttrLabelProxy "julianDays"
date_julianDays = AttrLabelProxy

#endif


-- | Get the value of the “@julian@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' date #julian
-- @
getDateJulian :: MonadIO m => Date -> m Word32
getDateJulian :: forall (m :: * -> *). MonadIO m => Date -> m Word32
getDateJulian Date
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
$ Date -> (Ptr Date -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Date
s ((Ptr Date -> IO Word32) -> IO Word32)
-> (Ptr Date -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr Date
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr Date
ptr Ptr Date -> 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 “@julian@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' date [ #julian 'Data.GI.Base.Attributes.:=' value ]
-- @
setDateJulian :: MonadIO m => Date -> Word32 -> m ()
setDateJulian :: forall (m :: * -> *). MonadIO m => Date -> Word32 -> m ()
setDateJulian Date
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
$ Date -> (Ptr Date -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Date
s ((Ptr Date -> IO ()) -> IO ()) -> (Ptr Date -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Date
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Date
ptr Ptr Date -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data DateJulianFieldInfo
instance AttrInfo DateJulianFieldInfo where
    type AttrBaseTypeConstraint DateJulianFieldInfo = (~) Date
    type AttrAllowedOps DateJulianFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DateJulianFieldInfo = (~) Word32
    type AttrTransferTypeConstraint DateJulianFieldInfo = (~)Word32
    type AttrTransferType DateJulianFieldInfo = Word32
    type AttrGetType DateJulianFieldInfo = Word32
    type AttrLabel DateJulianFieldInfo = "julian"
    type AttrOrigin DateJulianFieldInfo = Date
    attrGet = getDateJulian
    attrSet = setDateJulian
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.julian"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#g:attr:julian"
        })

date_julian :: AttrLabelProxy "julian"
date_julian = AttrLabelProxy

#endif


-- | Get the value of the “@dmy@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' date #dmy
-- @
getDateDmy :: MonadIO m => Date -> m Word32
getDateDmy :: forall (m :: * -> *). MonadIO m => Date -> m Word32
getDateDmy Date
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
$ Date -> (Ptr Date -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Date
s ((Ptr Date -> IO Word32) -> IO Word32)
-> (Ptr Date -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr Date
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr Date
ptr Ptr Date -> 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 “@dmy@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' date [ #dmy 'Data.GI.Base.Attributes.:=' value ]
-- @
setDateDmy :: MonadIO m => Date -> Word32 -> m ()
setDateDmy :: forall (m :: * -> *). MonadIO m => Date -> Word32 -> m ()
setDateDmy Date
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
$ Date -> (Ptr Date -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Date
s ((Ptr Date -> IO ()) -> IO ()) -> (Ptr Date -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Date
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Date
ptr Ptr Date -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data DateDmyFieldInfo
instance AttrInfo DateDmyFieldInfo where
    type AttrBaseTypeConstraint DateDmyFieldInfo = (~) Date
    type AttrAllowedOps DateDmyFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DateDmyFieldInfo = (~) Word32
    type AttrTransferTypeConstraint DateDmyFieldInfo = (~)Word32
    type AttrTransferType DateDmyFieldInfo = Word32
    type AttrGetType DateDmyFieldInfo = Word32
    type AttrLabel DateDmyFieldInfo = "dmy"
    type AttrOrigin DateDmyFieldInfo = Date
    attrGet = getDateDmy
    attrSet = setDateDmy
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dmy"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#g:attr:dmy"
        })

date_dmy :: AttrLabelProxy "dmy"
date_dmy = AttrLabelProxy

#endif


-- | Get the value of the “@day@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' date #day
-- @
getDateDay :: MonadIO m => Date -> m Word32
getDateDay :: forall (m :: * -> *). MonadIO m => Date -> m Word32
getDateDay Date
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
$ Date -> (Ptr Date -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Date
s ((Ptr Date -> IO Word32) -> IO Word32)
-> (Ptr Date -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr Date
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr Date
ptr Ptr Date -> 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 “@day@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' date [ #day 'Data.GI.Base.Attributes.:=' value ]
-- @
setDateDay :: MonadIO m => Date -> Word32 -> m ()
setDateDay :: forall (m :: * -> *). MonadIO m => Date -> Word32 -> m ()
setDateDay Date
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
$ Date -> (Ptr Date -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Date
s ((Ptr Date -> IO ()) -> IO ()) -> (Ptr Date -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Date
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Date
ptr Ptr Date -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data DateDayFieldInfo
instance AttrInfo DateDayFieldInfo where
    type AttrBaseTypeConstraint DateDayFieldInfo = (~) Date
    type AttrAllowedOps DateDayFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DateDayFieldInfo = (~) Word32
    type AttrTransferTypeConstraint DateDayFieldInfo = (~)Word32
    type AttrTransferType DateDayFieldInfo = Word32
    type AttrGetType DateDayFieldInfo = Word32
    type AttrLabel DateDayFieldInfo = "day"
    type AttrOrigin DateDayFieldInfo = Date
    attrGet = getDateDay
    attrSet = setDateDay
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.day"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#g:attr:day"
        })

date_day :: AttrLabelProxy "day"
date_day = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data DateMonthFieldInfo
instance AttrInfo DateMonthFieldInfo where
    type AttrBaseTypeConstraint DateMonthFieldInfo = (~) Date
    type AttrAllowedOps DateMonthFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DateMonthFieldInfo = (~) Word32
    type AttrTransferTypeConstraint DateMonthFieldInfo = (~)Word32
    type AttrTransferType DateMonthFieldInfo = Word32
    type AttrGetType DateMonthFieldInfo = Word32
    type AttrLabel DateMonthFieldInfo = "month"
    type AttrOrigin DateMonthFieldInfo = Date
    attrGet = getDateMonth
    attrSet = setDateMonth
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.month"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#g:attr:month"
        })

date_month :: AttrLabelProxy "month"
date_month = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data DateYearFieldInfo
instance AttrInfo DateYearFieldInfo where
    type AttrBaseTypeConstraint DateYearFieldInfo = (~) Date
    type AttrAllowedOps DateYearFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DateYearFieldInfo = (~) Word32
    type AttrTransferTypeConstraint DateYearFieldInfo = (~)Word32
    type AttrTransferType DateYearFieldInfo = Word32
    type AttrGetType DateYearFieldInfo = Word32
    type AttrLabel DateYearFieldInfo = "year"
    type AttrOrigin DateYearFieldInfo = Date
    attrGet = getDateYear
    attrSet = setDateYear
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.year"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#g:attr:year"
        })

date_year :: AttrLabelProxy "year"
date_year = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Date
type instance O.AttributeList Date = DateAttributeList
type DateAttributeList = ('[ '("julianDays", DateJulianDaysFieldInfo), '("julian", DateJulianFieldInfo), '("dmy", DateDmyFieldInfo), '("day", DateDayFieldInfo), '("month", DateMonthFieldInfo), '("year", DateYearFieldInfo)] :: [(Symbol, *)])
#endif

-- method Date::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Date" })
-- throws : False
-- Skip return : False

foreign import ccall "g_date_new" g_date_new :: 
    IO (Ptr Date)

-- | Allocates a t'GI.GLib.Structs.Date.Date' and initializes
-- it to a safe state. The new date will
-- be cleared (as if you\'d called 'GI.GLib.Structs.Date.dateClear') but invalid (it won\'t
-- represent an existing day). Free the return value with 'GI.GLib.Structs.Date.dateFree'.
dateNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Date
    -- ^ __Returns:__ a newly-allocated t'GI.GLib.Structs.Date.Date'
dateNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Date
dateNew  = IO Date -> m Date
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Date -> m Date) -> IO Date -> m Date
forall a b. (a -> b) -> a -> b
$ do
    Ptr Date
result <- IO (Ptr Date)
g_date_new
    Text -> Ptr Date -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dateNew" Ptr Date
result
    Date
result' <- ((ManagedPtr Date -> Date) -> Ptr Date -> IO Date
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Date -> Date
Date) Ptr Date
result
    Date -> IO Date
forall (m :: * -> *) a. Monad m => a -> m a
return Date
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Date::new_dmy
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "day"
--           , argType = TBasicType TUInt8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "day of the month" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "month"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DateMonth" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "month of the year" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "year"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "year" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Date" })
-- throws : False
-- Skip return : False

foreign import ccall "g_date_new_dmy" g_date_new_dmy :: 
    Word8 ->                                -- day : TBasicType TUInt8
    CUInt ->                                -- month : TInterface (Name {namespace = "GLib", name = "DateMonth"})
    Word16 ->                               -- year : TBasicType TUInt16
    IO (Ptr Date)

-- | Like 'GI.GLib.Structs.Date.dateNew', but also sets the value of the date. Assuming the
-- day-month-year triplet you pass in represents an existing day, the
-- returned date will be valid.
dateNewDmy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word8
    -- ^ /@day@/: day of the month
    -> GLib.Enums.DateMonth
    -- ^ /@month@/: month of the year
    -> Word16
    -- ^ /@year@/: year
    -> m Date
    -- ^ __Returns:__ a newly-allocated t'GI.GLib.Structs.Date.Date' initialized with /@day@/, /@month@/, and /@year@/
dateNewDmy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Word8 -> DateMonth -> Word16 -> m Date
dateNewDmy Word8
day DateMonth
month Word16
year = IO Date -> m Date
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Date -> m Date) -> IO Date -> m Date
forall a b. (a -> b) -> a -> b
$ do
    let month' :: CUInt
month' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (DateMonth -> Int) -> DateMonth -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DateMonth -> Int
forall a. Enum a => a -> Int
fromEnum) DateMonth
month
    Ptr Date
result <- Word8 -> CUInt -> Word16 -> IO (Ptr Date)
g_date_new_dmy Word8
day CUInt
month' Word16
year
    Text -> Ptr Date -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dateNewDmy" Ptr Date
result
    Date
result' <- ((ManagedPtr Date -> Date) -> Ptr Date -> IO Date
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Date -> Date
Date) Ptr Date
result
    Date -> IO Date
forall (m :: * -> *) a. Monad m => a -> m a
return Date
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Date::new_julian
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "julian_day"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "days since January 1, Year 1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Date" })
-- throws : False
-- Skip return : False

foreign import ccall "g_date_new_julian" g_date_new_julian :: 
    Word32 ->                               -- julian_day : TBasicType TUInt32
    IO (Ptr Date)

-- | Like 'GI.GLib.Structs.Date.dateNew', but also sets the value of the date. Assuming the
-- Julian day number you pass in is valid (greater than 0, less than an
-- unreasonably large number), the returned date will be valid.
dateNewJulian ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word32
    -- ^ /@julianDay@/: days since January 1, Year 1
    -> m Date
    -- ^ __Returns:__ a newly-allocated t'GI.GLib.Structs.Date.Date' initialized with /@julianDay@/
dateNewJulian :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Word32 -> m Date
dateNewJulian Word32
julianDay = IO Date -> m Date
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Date -> m Date) -> IO Date -> m Date
forall a b. (a -> b) -> a -> b
$ do
    Ptr Date
result <- Word32 -> IO (Ptr Date)
g_date_new_julian Word32
julianDay
    Text -> Ptr Date -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dateNewJulian" Ptr Date
result
    Date
result' <- ((ManagedPtr Date -> Date) -> Ptr Date -> IO Date
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Date -> Date
Date) Ptr Date
result
    Date -> IO Date
forall (m :: * -> *) a. Monad m => a -> m a
return Date
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Date::add_days
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to increment"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_days"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of days to move the date forward"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_add_days" g_date_add_days :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Word32 ->                               -- n_days : TBasicType TUInt
    IO ()

-- | Increments a date some number of days.
-- To move forward by weeks, add weeks*7 days.
-- The date must be valid.
dateAddDays ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to increment
    -> Word32
    -- ^ /@nDays@/: number of days to move the date forward
    -> m ()
dateAddDays :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Word32 -> m ()
dateAddDays Date
date Word32
nDays = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date -> Word32 -> IO ()
g_date_add_days Ptr Date
date' Word32
nDays
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateAddDaysMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.OverloadedMethod DateAddDaysMethodInfo Date signature where
    overloadedMethod = dateAddDays

instance O.OverloadedMethodInfo DateAddDaysMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateAddDays",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateAddDays"
        })


#endif

-- method Date::add_months
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to increment"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_months"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of months to move forward"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_add_months" g_date_add_months :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Word32 ->                               -- n_months : TBasicType TUInt
    IO ()

-- | Increments a date by some number of months.
-- If the day of the month is greater than 28,
-- this routine may change the day of the month
-- (because the destination month may not have
-- the current day in it). The date must be valid.
dateAddMonths ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to increment
    -> Word32
    -- ^ /@nMonths@/: number of months to move forward
    -> m ()
dateAddMonths :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Word32 -> m ()
dateAddMonths Date
date Word32
nMonths = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date -> Word32 -> IO ()
g_date_add_months Ptr Date
date' Word32
nMonths
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateAddMonthsMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.OverloadedMethod DateAddMonthsMethodInfo Date signature where
    overloadedMethod = dateAddMonths

instance O.OverloadedMethodInfo DateAddMonthsMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateAddMonths",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateAddMonths"
        })


#endif

-- method Date::add_years
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to increment"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_years"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of years to move forward"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_add_years" g_date_add_years :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Word32 ->                               -- n_years : TBasicType TUInt
    IO ()

-- | Increments a date by some number of years.
-- If the date is February 29, and the destination
-- year is not a leap year, the date will be changed
-- to February 28. The date must be valid.
dateAddYears ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to increment
    -> Word32
    -- ^ /@nYears@/: number of years to move forward
    -> m ()
dateAddYears :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Word32 -> m ()
dateAddYears Date
date Word32
nYears = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date -> Word32 -> IO ()
g_date_add_years Ptr Date
date' Word32
nYears
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateAddYearsMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.OverloadedMethod DateAddYearsMethodInfo Date signature where
    overloadedMethod = dateAddYears

instance O.OverloadedMethodInfo DateAddYearsMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateAddYears",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateAddYears"
        })


#endif

-- method Date::clamp
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to clamp" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "min_date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "minimum accepted value for @date"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "max_date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "maximum accepted value for @date"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_clamp" g_date_clamp :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Ptr Date ->                             -- min_date : TInterface (Name {namespace = "GLib", name = "Date"})
    Ptr Date ->                             -- max_date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO ()

-- | If /@date@/ is prior to /@minDate@/, sets /@date@/ equal to /@minDate@/.
-- If /@date@/ falls after /@maxDate@/, sets /@date@/ equal to /@maxDate@/.
-- Otherwise, /@date@/ is unchanged.
-- Either of /@minDate@/ and /@maxDate@/ may be 'P.Nothing'.
-- All non-'P.Nothing' dates must be valid.
dateClamp ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to clamp
    -> Date
    -- ^ /@minDate@/: minimum accepted value for /@date@/
    -> Date
    -- ^ /@maxDate@/: maximum accepted value for /@date@/
    -> m ()
dateClamp :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Date -> Date -> m ()
dateClamp Date
date Date
minDate Date
maxDate = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date
minDate' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
minDate
    Ptr Date
maxDate' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
maxDate
    Ptr Date -> Ptr Date -> Ptr Date -> IO ()
g_date_clamp Ptr Date
date' Ptr Date
minDate' Ptr Date
maxDate'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
minDate
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
maxDate
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateClampMethodInfo
instance (signature ~ (Date -> Date -> m ()), MonadIO m) => O.OverloadedMethod DateClampMethodInfo Date signature where
    overloadedMethod = dateClamp

instance O.OverloadedMethodInfo DateClampMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateClamp",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateClamp"
        })


#endif

-- method Date::clear
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer to one or more dates to clear"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_dates"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of dates to clear"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_clear" g_date_clear :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Word32 ->                               -- n_dates : TBasicType TUInt
    IO ()

-- | Initializes one or more t'GI.GLib.Structs.Date.Date' structs to a safe but invalid
-- state. The cleared dates will not represent an existing date, but will
-- not contain garbage. Useful to init a date declared on the stack.
-- Validity can be tested with 'GI.GLib.Structs.Date.dateValid'.
dateClear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: pointer to one or more dates to clear
    -> Word32
    -- ^ /@nDates@/: number of dates to clear
    -> m ()
dateClear :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Word32 -> m ()
dateClear Date
date Word32
nDates = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date -> Word32 -> IO ()
g_date_clear Ptr Date
date' Word32
nDates
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateClearMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.OverloadedMethod DateClearMethodInfo Date signature where
    overloadedMethod = dateClear

instance O.OverloadedMethodInfo DateClearMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateClear",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateClear"
        })


#endif

-- method Date::compare
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "lhs"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "first date to compare"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rhs"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "second date to compare"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_date_compare" g_date_compare :: 
    Ptr Date ->                             -- lhs : TInterface (Name {namespace = "GLib", name = "Date"})
    Ptr Date ->                             -- rhs : TInterface (Name {namespace = "GLib", name = "Date"})
    IO Int32

-- | @/qsort()/@-style comparison function for dates.
-- Both dates must be valid.
dateCompare ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@lhs@/: first date to compare
    -> Date
    -- ^ /@rhs@/: second date to compare
    -> m Int32
    -- ^ __Returns:__ 0 for equal, less than zero if /@lhs@/ is less than /@rhs@/,
    --     greater than zero if /@lhs@/ is greater than /@rhs@/
dateCompare :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Date -> m Int32
dateCompare Date
lhs Date
rhs = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Date
lhs' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
lhs
    Ptr Date
rhs' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
rhs
    Int32
result <- Ptr Date -> Ptr Date -> IO Int32
g_date_compare Ptr Date
lhs' Ptr Date
rhs'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
lhs
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
rhs
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data DateCompareMethodInfo
instance (signature ~ (Date -> m Int32), MonadIO m) => O.OverloadedMethod DateCompareMethodInfo Date signature where
    overloadedMethod = dateCompare

instance O.OverloadedMethodInfo DateCompareMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateCompare",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateCompare"
        })


#endif

-- method Date::copy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to copy" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Date" })
-- throws : False
-- Skip return : False

foreign import ccall "g_date_copy" g_date_copy :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO (Ptr Date)

-- | Copies a GDate to a newly-allocated GDate. If the input was invalid
-- (as determined by 'GI.GLib.Structs.Date.dateValid'), the invalid state will be copied
-- as is into the new object.
-- 
-- /Since: 2.56/
dateCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to copy
    -> m Date
    -- ^ __Returns:__ a newly-allocated t'GI.GLib.Structs.Date.Date' initialized from /@date@/
dateCopy :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Date -> m Date
dateCopy Date
date = IO Date -> m Date
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Date -> m Date) -> IO Date -> m Date
forall a b. (a -> b) -> a -> b
$ do
    Ptr Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date
result <- Ptr Date -> IO (Ptr Date)
g_date_copy Ptr Date
date'
    Text -> Ptr Date -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dateCopy" Ptr Date
result
    Date
result' <- ((ManagedPtr Date -> Date) -> Ptr Date -> IO Date
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Date -> Date
Date) Ptr Date
result
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    Date -> IO Date
forall (m :: * -> *) a. Monad m => a -> m a
return Date
result'

#if defined(ENABLE_OVERLOADING)
data DateCopyMethodInfo
instance (signature ~ (m Date), MonadIO m) => O.OverloadedMethod DateCopyMethodInfo Date signature where
    overloadedMethod = dateCopy

instance O.OverloadedMethodInfo DateCopyMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateCopy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateCopy"
        })


#endif

-- method Date::days_between
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date1"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the first date" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "date2"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the second date" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_date_days_between" g_date_days_between :: 
    Ptr Date ->                             -- date1 : TInterface (Name {namespace = "GLib", name = "Date"})
    Ptr Date ->                             -- date2 : TInterface (Name {namespace = "GLib", name = "Date"})
    IO Int32

-- | Computes the number of days between two dates.
-- If /@date2@/ is prior to /@date1@/, the returned value is negative.
-- Both dates must be valid.
dateDaysBetween ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date1@/: the first date
    -> Date
    -- ^ /@date2@/: the second date
    -> m Int32
    -- ^ __Returns:__ the number of days between /@date1@/ and /@date2@/
dateDaysBetween :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Date -> m Int32
dateDaysBetween Date
date1 Date
date2 = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Date
date1' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date1
    Ptr Date
date2' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date2
    Int32
result <- Ptr Date -> Ptr Date -> IO Int32
g_date_days_between Ptr Date
date1' Ptr Date
date2'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date1
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date2
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data DateDaysBetweenMethodInfo
instance (signature ~ (Date -> m Int32), MonadIO m) => O.OverloadedMethod DateDaysBetweenMethodInfo Date signature where
    overloadedMethod = dateDaysBetween

instance O.OverloadedMethodInfo DateDaysBetweenMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateDaysBetween",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateDaysBetween"
        })


#endif

-- method Date::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to free" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_free" g_date_free :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO ()

-- | Frees a t'GI.GLib.Structs.Date.Date' returned from 'GI.GLib.Structs.Date.dateNew'.
dateFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to free
    -> m ()
dateFree :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Date -> m ()
dateFree Date
date = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date -> IO ()
g_date_free Ptr Date
date'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod DateFreeMethodInfo Date signature where
    overloadedMethod = dateFree

instance O.OverloadedMethodInfo DateFreeMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateFree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateFree"
        })


#endif

-- method Date::get_day
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to extract the day of the month from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt8)
-- throws : False
-- Skip return : False

foreign import ccall "g_date_get_day" g_date_get_day :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO Word8

-- | Returns the day of the month. The date must be valid.
dateGetDay ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to extract the day of the month from
    -> m Word8
    -- ^ __Returns:__ day of the month
dateGetDay :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Date -> m Word8
dateGetDay Date
date = IO Word8 -> m Word8
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word8 -> m Word8) -> IO Word8 -> m Word8
forall a b. (a -> b) -> a -> b
$ do
    Ptr Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Word8
result <- Ptr Date -> IO Word8
g_date_get_day Ptr Date
date'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    Word8 -> IO Word8
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
result

#if defined(ENABLE_OVERLOADING)
data DateGetDayMethodInfo
instance (signature ~ (m Word8), MonadIO m) => O.OverloadedMethod DateGetDayMethodInfo Date signature where
    overloadedMethod = dateGetDay

instance O.OverloadedMethodInfo DateGetDayMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateGetDay",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateGetDay"
        })


#endif

-- method Date::get_day_of_year
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to extract day of year from"
--                 , 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_date_get_day_of_year" g_date_get_day_of_year :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO Word32

-- | Returns the day of the year, where Jan 1 is the first day of the
-- year. The date must be valid.
dateGetDayOfYear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to extract day of year from
    -> m Word32
    -- ^ __Returns:__ day of the year
dateGetDayOfYear :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Date -> m Word32
dateGetDayOfYear Date
date = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Word32
result <- Ptr Date -> IO Word32
g_date_get_day_of_year Ptr Date
date'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data DateGetDayOfYearMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod DateGetDayOfYearMethodInfo Date signature where
    overloadedMethod = dateGetDayOfYear

instance O.OverloadedMethodInfo DateGetDayOfYearMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateGetDayOfYear",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateGetDayOfYear"
        })


#endif

-- method Date::get_iso8601_week_of_year
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid #GDate" , 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_date_get_iso8601_week_of_year" g_date_get_iso8601_week_of_year :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO Word32

-- | Returns the week of the year, where weeks are interpreted according
-- to ISO 8601.
-- 
-- /Since: 2.6/
dateGetIso8601WeekOfYear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a valid t'GI.GLib.Structs.Date.Date'
    -> m Word32
    -- ^ __Returns:__ ISO 8601 week number of the year.
dateGetIso8601WeekOfYear :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Date -> m Word32
dateGetIso8601WeekOfYear Date
date = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Word32
result <- Ptr Date -> IO Word32
g_date_get_iso8601_week_of_year Ptr Date
date'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data DateGetIso8601WeekOfYearMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod DateGetIso8601WeekOfYearMethodInfo Date signature where
    overloadedMethod = dateGetIso8601WeekOfYear

instance O.OverloadedMethodInfo DateGetIso8601WeekOfYearMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateGetIso8601WeekOfYear",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateGetIso8601WeekOfYear"
        })


#endif

-- method Date::get_julian
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to extract the Julian day from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt32)
-- throws : False
-- Skip return : False

foreign import ccall "g_date_get_julian" g_date_get_julian :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO Word32

-- | Returns the Julian day or \"serial number\" of the t'GI.GLib.Structs.Date.Date'. The
-- Julian day is simply the number of days since January 1, Year 1; i.e.,
-- January 1, Year 1 is Julian day 1; January 2, Year 1 is Julian day 2,
-- etc. The date must be valid.
dateGetJulian ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to extract the Julian day from
    -> m Word32
    -- ^ __Returns:__ Julian day
dateGetJulian :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Date -> m Word32
dateGetJulian Date
date = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Word32
result <- Ptr Date -> IO Word32
g_date_get_julian Ptr Date
date'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data DateGetJulianMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod DateGetJulianMethodInfo Date signature where
    overloadedMethod = dateGetJulian

instance O.OverloadedMethodInfo DateGetJulianMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateGetJulian",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateGetJulian"
        })


#endif

-- method Date::get_monday_week_of_year
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate" , 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_date_get_monday_week_of_year" g_date_get_monday_week_of_year :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO Word32

-- | Returns the week of the year, where weeks are understood to start on
-- Monday. If the date is before the first Monday of the year, return 0.
-- The date must be valid.
dateGetMondayWeekOfYear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date'
    -> m Word32
    -- ^ __Returns:__ week of the year
dateGetMondayWeekOfYear :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Date -> m Word32
dateGetMondayWeekOfYear Date
date = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Word32
result <- Ptr Date -> IO Word32
g_date_get_monday_week_of_year Ptr Date
date'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data DateGetMondayWeekOfYearMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod DateGetMondayWeekOfYearMethodInfo Date signature where
    overloadedMethod = dateGetMondayWeekOfYear

instance O.OverloadedMethodInfo DateGetMondayWeekOfYearMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateGetMondayWeekOfYear",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateGetMondayWeekOfYear"
        })


#endif

-- method Date::get_month
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to get the month from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "DateMonth" })
-- throws : False
-- Skip return : False

foreign import ccall "g_date_get_month" g_date_get_month :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO CUInt

-- | Returns the month of the year. The date must be valid.
dateGetMonth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to get the month from
    -> m GLib.Enums.DateMonth
    -- ^ __Returns:__ month of the year as a t'GI.GLib.Enums.DateMonth'
dateGetMonth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> m DateMonth
dateGetMonth Date
date = IO DateMonth -> m DateMonth
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DateMonth -> m DateMonth) -> IO DateMonth -> m DateMonth
forall a b. (a -> b) -> a -> b
$ do
    Ptr Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    CUInt
result <- Ptr Date -> IO CUInt
g_date_get_month Ptr Date
date'
    let result' :: DateMonth
result' = (Int -> DateMonth
forall a. Enum a => Int -> a
toEnum (Int -> DateMonth) -> (CUInt -> Int) -> CUInt -> DateMonth
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    DateMonth -> IO DateMonth
forall (m :: * -> *) a. Monad m => a -> m a
return DateMonth
result'

#if defined(ENABLE_OVERLOADING)
data DateGetMonthMethodInfo
instance (signature ~ (m GLib.Enums.DateMonth), MonadIO m) => O.OverloadedMethod DateGetMonthMethodInfo Date signature where
    overloadedMethod = dateGetMonth

instance O.OverloadedMethodInfo DateGetMonthMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateGetMonth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateGetMonth"
        })


#endif

-- method Date::get_sunday_week_of_year
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate" , 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_date_get_sunday_week_of_year" g_date_get_sunday_week_of_year :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO Word32

-- | Returns the week of the year during which this date falls, if
-- weeks are understood to begin on Sunday. The date must be valid.
-- Can return 0 if the day is before the first Sunday of the year.
dateGetSundayWeekOfYear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date'
    -> m Word32
    -- ^ __Returns:__ week number
dateGetSundayWeekOfYear :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Date -> m Word32
dateGetSundayWeekOfYear Date
date = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Word32
result <- Ptr Date -> IO Word32
g_date_get_sunday_week_of_year Ptr Date
date'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data DateGetSundayWeekOfYearMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod DateGetSundayWeekOfYearMethodInfo Date signature where
    overloadedMethod = dateGetSundayWeekOfYear

instance O.OverloadedMethodInfo DateGetSundayWeekOfYearMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateGetSundayWeekOfYear",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateGetSundayWeekOfYear"
        })


#endif

-- method Date::get_weekday
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GLib" , name = "DateWeekday" })
-- throws : False
-- Skip return : False

foreign import ccall "g_date_get_weekday" g_date_get_weekday :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO CUInt

-- | Returns the day of the week for a t'GI.GLib.Structs.Date.Date'. The date must be valid.
dateGetWeekday ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date'
    -> m GLib.Enums.DateWeekday
    -- ^ __Returns:__ day of the week as a t'GI.GLib.Enums.DateWeekday'.
dateGetWeekday :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> m DateWeekday
dateGetWeekday Date
date = IO DateWeekday -> m DateWeekday
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DateWeekday -> m DateWeekday)
-> IO DateWeekday -> m DateWeekday
forall a b. (a -> b) -> a -> b
$ do
    Ptr Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    CUInt
result <- Ptr Date -> IO CUInt
g_date_get_weekday Ptr Date
date'
    let result' :: DateWeekday
result' = (Int -> DateWeekday
forall a. Enum a => Int -> a
toEnum (Int -> DateWeekday) -> (CUInt -> Int) -> CUInt -> DateWeekday
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    DateWeekday -> IO DateWeekday
forall (m :: * -> *) a. Monad m => a -> m a
return DateWeekday
result'

#if defined(ENABLE_OVERLOADING)
data DateGetWeekdayMethodInfo
instance (signature ~ (m GLib.Enums.DateWeekday), MonadIO m) => O.OverloadedMethod DateGetWeekdayMethodInfo Date signature where
    overloadedMethod = dateGetWeekday

instance O.OverloadedMethodInfo DateGetWeekdayMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateGetWeekday",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateGetWeekday"
        })


#endif

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

foreign import ccall "g_date_get_year" g_date_get_year :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO Word16

-- | Returns the year of a t'GI.GLib.Structs.Date.Date'. The date must be valid.
dateGetYear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date'
    -> m Word16
    -- ^ __Returns:__ year in which the date falls
dateGetYear :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Date -> m Word16
dateGetYear Date
date = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ do
    Ptr Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Word16
result <- Ptr Date -> IO Word16
g_date_get_year Ptr Date
date'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
result

#if defined(ENABLE_OVERLOADING)
data DateGetYearMethodInfo
instance (signature ~ (m Word16), MonadIO m) => O.OverloadedMethod DateGetYearMethodInfo Date signature where
    overloadedMethod = dateGetYear

instance O.OverloadedMethodInfo DateGetYearMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateGetYear",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateGetYear"
        })


#endif

-- method Date::is_first_of_month
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to check" , 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_date_is_first_of_month" g_date_is_first_of_month :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO CInt

-- | Returns 'P.True' if the date is on the first of a month.
-- The date must be valid.
dateIsFirstOfMonth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to check
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the date is the first of the month
dateIsFirstOfMonth :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Date -> m Bool
dateIsFirstOfMonth Date
date = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    CInt
result <- Ptr Date -> IO CInt
g_date_is_first_of_month Ptr Date
date'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DateIsFirstOfMonthMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod DateIsFirstOfMonthMethodInfo Date signature where
    overloadedMethod = dateIsFirstOfMonth

instance O.OverloadedMethodInfo DateIsFirstOfMonthMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateIsFirstOfMonth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateIsFirstOfMonth"
        })


#endif

-- method Date::is_last_of_month
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to check" , 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_date_is_last_of_month" g_date_is_last_of_month :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO CInt

-- | Returns 'P.True' if the date is the last day of the month.
-- The date must be valid.
dateIsLastOfMonth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to check
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the date is the last day of the month
dateIsLastOfMonth :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Date -> m Bool
dateIsLastOfMonth Date
date = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    CInt
result <- Ptr Date -> IO CInt
g_date_is_last_of_month Ptr Date
date'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DateIsLastOfMonthMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod DateIsLastOfMonthMethodInfo Date signature where
    overloadedMethod = dateIsLastOfMonth

instance O.OverloadedMethodInfo DateIsLastOfMonthMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateIsLastOfMonth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateIsLastOfMonth"
        })


#endif

-- method Date::order
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date1"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the first date" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "date2"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the second date" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_order" g_date_order :: 
    Ptr Date ->                             -- date1 : TInterface (Name {namespace = "GLib", name = "Date"})
    Ptr Date ->                             -- date2 : TInterface (Name {namespace = "GLib", name = "Date"})
    IO ()

-- | Checks if /@date1@/ is less than or equal to /@date2@/,
-- and swap the values if this is not the case.
dateOrder ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date1@/: the first date
    -> Date
    -- ^ /@date2@/: the second date
    -> m ()
dateOrder :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Date -> m ()
dateOrder Date
date1 Date
date2 = 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 Date
date1' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date1
    Ptr Date
date2' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date2
    Ptr Date -> Ptr Date -> IO ()
g_date_order Ptr Date
date1' Ptr Date
date2'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date1
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date2
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateOrderMethodInfo
instance (signature ~ (Date -> m ()), MonadIO m) => O.OverloadedMethod DateOrderMethodInfo Date signature where
    overloadedMethod = dateOrder

instance O.OverloadedMethodInfo DateOrderMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateOrder",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateOrder"
        })


#endif

-- method Date::set_day
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "day"
--           , argType = TBasicType TUInt8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "day to set" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_set_day" g_date_set_day :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Word8 ->                                -- day : TBasicType TUInt8
    IO ()

-- | Sets the day of the month for a t'GI.GLib.Structs.Date.Date'. If the resulting
-- day-month-year triplet is invalid, the date will be invalid.
dateSetDay ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date'
    -> Word8
    -- ^ /@day@/: day to set
    -> m ()
dateSetDay :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Word8 -> m ()
dateSetDay Date
date Word8
day = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date -> Word8 -> IO ()
g_date_set_day Ptr Date
date' Word8
day
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateSetDayMethodInfo
instance (signature ~ (Word8 -> m ()), MonadIO m) => O.OverloadedMethod DateSetDayMethodInfo Date signature where
    overloadedMethod = dateSetDay

instance O.OverloadedMethodInfo DateSetDayMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateSetDay",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateSetDay"
        })


#endif

-- method Date::set_dmy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "day"
--           , argType = TBasicType TUInt8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "day" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "month"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DateMonth" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "month" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "year" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_set_dmy" g_date_set_dmy :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Word8 ->                                -- day : TBasicType TUInt8
    CUInt ->                                -- month : TInterface (Name {namespace = "GLib", name = "DateMonth"})
    Word16 ->                               -- y : TBasicType TUInt16
    IO ()

-- | Sets the value of a t'GI.GLib.Structs.Date.Date' from a day, month, and year.
-- The day-month-year triplet must be valid; if you aren\'t
-- sure it is, call 'GI.GLib.Functions.dateValidDmy' to check before you
-- set it.
dateSetDmy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date'
    -> Word8
    -- ^ /@day@/: day
    -> GLib.Enums.DateMonth
    -- ^ /@month@/: month
    -> Word16
    -- ^ /@y@/: year
    -> m ()
dateSetDmy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Word8 -> DateMonth -> Word16 -> m ()
dateSetDmy Date
date Word8
day DateMonth
month Word16
y = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    let month' :: CUInt
month' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (DateMonth -> Int) -> DateMonth -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DateMonth -> Int
forall a. Enum a => a -> Int
fromEnum) DateMonth
month
    Ptr Date -> Word8 -> CUInt -> Word16 -> IO ()
g_date_set_dmy Ptr Date
date' Word8
day CUInt
month' Word16
y
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateSetDmyMethodInfo
instance (signature ~ (Word8 -> GLib.Enums.DateMonth -> Word16 -> m ()), MonadIO m) => O.OverloadedMethod DateSetDmyMethodInfo Date signature where
    overloadedMethod = dateSetDmy

instance O.OverloadedMethodInfo DateSetDmyMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateSetDmy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateSetDmy"
        })


#endif

-- method Date::set_julian
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "julian_date"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Julian day number (days since January 1, Year 1)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_set_julian" g_date_set_julian :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Word32 ->                               -- julian_date : TBasicType TUInt32
    IO ()

-- | Sets the value of a t'GI.GLib.Structs.Date.Date' from a Julian day number.
dateSetJulian ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date'
    -> Word32
    -- ^ /@julianDate@/: Julian day number (days since January 1, Year 1)
    -> m ()
dateSetJulian :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Word32 -> m ()
dateSetJulian Date
date Word32
julianDate = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date -> Word32 -> IO ()
g_date_set_julian Ptr Date
date' Word32
julianDate
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateSetJulianMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.OverloadedMethod DateSetJulianMethodInfo Date signature where
    overloadedMethod = dateSetJulian

instance O.OverloadedMethodInfo DateSetJulianMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateSetJulian",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateSetJulian"
        })


#endif

-- method Date::set_month
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "month"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DateMonth" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "month to set" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_set_month" g_date_set_month :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    CUInt ->                                -- month : TInterface (Name {namespace = "GLib", name = "DateMonth"})
    IO ()

-- | Sets the month of the year for a t'GI.GLib.Structs.Date.Date'.  If the resulting
-- day-month-year triplet is invalid, the date will be invalid.
dateSetMonth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date'
    -> GLib.Enums.DateMonth
    -- ^ /@month@/: month to set
    -> m ()
dateSetMonth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> DateMonth -> m ()
dateSetMonth Date
date DateMonth
month = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    let month' :: CUInt
month' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (DateMonth -> Int) -> DateMonth -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DateMonth -> Int
forall a. Enum a => a -> Int
fromEnum) DateMonth
month
    Ptr Date -> CUInt -> IO ()
g_date_set_month Ptr Date
date' CUInt
month'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateSetMonthMethodInfo
instance (signature ~ (GLib.Enums.DateMonth -> m ()), MonadIO m) => O.OverloadedMethod DateSetMonthMethodInfo Date signature where
    overloadedMethod = dateSetMonth

instance O.OverloadedMethodInfo DateSetMonthMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateSetMonth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateSetMonth"
        })


#endif

-- method Date::set_parse
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to fill in"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "str"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "string to parse" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_set_parse" g_date_set_parse :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    CString ->                              -- str : TBasicType TUTF8
    IO ()

-- | Parses a user-inputted string /@str@/, and try to figure out what date it
-- represents, taking the [current locale][setlocale] into account. If the
-- string is successfully parsed, the date will be valid after the call.
-- Otherwise, it will be invalid. You should check using 'GI.GLib.Structs.Date.dateValid'
-- to see whether the parsing succeeded.
-- 
-- This function is not appropriate for file formats and the like; it
-- isn\'t very precise, and its exact behavior varies with the locale.
-- It\'s intended to be a heuristic routine that guesses what the user
-- means by a given string (and it does work pretty well in that
-- capacity).
dateSetParse ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to fill in
    -> T.Text
    -- ^ /@str@/: string to parse
    -> m ()
dateSetParse :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Text -> m ()
dateSetParse Date
date Text
str = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    CString
str' <- Text -> IO CString
textToCString Text
str
    Ptr Date -> CString -> IO ()
g_date_set_parse Ptr Date
date' CString
str'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateSetParseMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod DateSetParseMethodInfo Date signature where
    overloadedMethod = dateSetParse

instance O.OverloadedMethodInfo DateSetParseMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateSetParse",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateSetParse"
        })


#endif

-- method Date::set_time
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "time_"
--           , argType = TBasicType TInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GTime value to set."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_set_time" g_date_set_time :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Int32 ->                                -- time_ : TBasicType TInt32
    IO ()

{-# DEPRECATED dateSetTime ["(Since version 2.10)","Use 'GI.GLib.Structs.Date.dateSetTimeT' instead."] #-}
-- | Sets the value of a date from a @/GTime/@ value.
-- The time to date conversion is done using the user\'s current timezone.
dateSetTime ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date'.
    -> Int32
    -- ^ /@time_@/: @/GTime/@ value to set.
    -> m ()
dateSetTime :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Int32 -> m ()
dateSetTime Date
date Int32
time_ = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date -> Int32 -> IO ()
g_date_set_time Ptr Date
date' Int32
time_
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateSetTimeMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m) => O.OverloadedMethod DateSetTimeMethodInfo Date signature where
    overloadedMethod = dateSetTime

instance O.OverloadedMethodInfo DateSetTimeMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateSetTime",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateSetTime"
        })


#endif

-- method Date::set_time_t
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timet"
--           , argType = TBasicType TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "time_t value to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_set_time_t" g_date_set_time_t :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    CLong ->                                -- timet : TBasicType TLong
    IO ()

-- | Sets the value of a date to the date corresponding to a time
-- specified as a time_t. The time to date conversion is done using
-- the user\'s current timezone.
-- 
-- To set the value of a date to the current day, you could write:
-- 
-- === /C code/
-- >
-- > time_t now = time (NULL);
-- > if (now == (time_t) -1)
-- >   // handle the error
-- > g_date_set_time_t (date, now);
-- 
-- 
-- /Since: 2.10/
dateSetTimeT ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date'
    -> CLong
    -- ^ /@timet@/: time_t value to set
    -> m ()
dateSetTimeT :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> CLong -> m ()
dateSetTimeT Date
date CLong
timet = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date -> CLong -> IO ()
g_date_set_time_t Ptr Date
date' CLong
timet
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateSetTimeTMethodInfo
instance (signature ~ (CLong -> m ()), MonadIO m) => O.OverloadedMethod DateSetTimeTMethodInfo Date signature where
    overloadedMethod = dateSetTimeT

instance O.OverloadedMethodInfo DateSetTimeTMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateSetTimeT",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateSetTimeT"
        })


#endif

-- method Date::set_time_val
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeval"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "TimeVal" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GTimeVal value to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_set_time_val" g_date_set_time_val :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Ptr GLib.TimeVal.TimeVal ->             -- timeval : TInterface (Name {namespace = "GLib", name = "TimeVal"})
    IO ()

{-# DEPRECATED dateSetTimeVal ["(Since version 2.62)","t'GI.GLib.Structs.TimeVal.TimeVal' is not year-2038-safe. Use 'GI.GLib.Structs.Date.dateSetTimeT'","   instead."] #-}
-- | Sets the value of a date from a t'GI.GLib.Structs.TimeVal.TimeVal' value.  Note that the
-- /@tvUsec@/ member is ignored, because t'GI.GLib.Structs.Date.Date' can\'t make use of the
-- additional precision.
-- 
-- The time to date conversion is done using the user\'s current timezone.
-- 
-- /Since: 2.10/
dateSetTimeVal ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date'
    -> GLib.TimeVal.TimeVal
    -- ^ /@timeval@/: t'GI.GLib.Structs.TimeVal.TimeVal' value to set
    -> m ()
dateSetTimeVal :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> TimeVal -> m ()
dateSetTimeVal Date
date TimeVal
timeval = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr TimeVal
timeval' <- TimeVal -> IO (Ptr TimeVal)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TimeVal
timeval
    Ptr Date -> Ptr TimeVal -> IO ()
g_date_set_time_val Ptr Date
date' Ptr TimeVal
timeval'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    TimeVal -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TimeVal
timeval
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateSetTimeValMethodInfo
instance (signature ~ (GLib.TimeVal.TimeVal -> m ()), MonadIO m) => O.OverloadedMethod DateSetTimeValMethodInfo Date signature where
    overloadedMethod = dateSetTimeVal

instance O.OverloadedMethodInfo DateSetTimeValMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateSetTimeVal",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateSetTimeVal"
        })


#endif

-- method Date::set_year
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "year"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "year to set" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_set_year" g_date_set_year :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Word16 ->                               -- year : TBasicType TUInt16
    IO ()

-- | Sets the year for a t'GI.GLib.Structs.Date.Date'. If the resulting day-month-year
-- triplet is invalid, the date will be invalid.
dateSetYear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date'
    -> Word16
    -- ^ /@year@/: year to set
    -> m ()
dateSetYear :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Word16 -> m ()
dateSetYear Date
date Word16
year = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date -> Word16 -> IO ()
g_date_set_year Ptr Date
date' Word16
year
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateSetYearMethodInfo
instance (signature ~ (Word16 -> m ()), MonadIO m) => O.OverloadedMethod DateSetYearMethodInfo Date signature where
    overloadedMethod = dateSetYear

instance O.OverloadedMethodInfo DateSetYearMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateSetYear",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateSetYear"
        })


#endif

-- method Date::subtract_days
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to decrement"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_days"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of days to move"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_subtract_days" g_date_subtract_days :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Word32 ->                               -- n_days : TBasicType TUInt
    IO ()

-- | Moves a date some number of days into the past.
-- To move by weeks, just move by weeks*7 days.
-- The date must be valid.
dateSubtractDays ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to decrement
    -> Word32
    -- ^ /@nDays@/: number of days to move
    -> m ()
dateSubtractDays :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Word32 -> m ()
dateSubtractDays Date
date Word32
nDays = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date -> Word32 -> IO ()
g_date_subtract_days Ptr Date
date' Word32
nDays
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateSubtractDaysMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.OverloadedMethod DateSubtractDaysMethodInfo Date signature where
    overloadedMethod = dateSubtractDays

instance O.OverloadedMethodInfo DateSubtractDaysMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateSubtractDays",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateSubtractDays"
        })


#endif

-- method Date::subtract_months
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to decrement"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_months"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of months to move"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_subtract_months" g_date_subtract_months :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Word32 ->                               -- n_months : TBasicType TUInt
    IO ()

-- | Moves a date some number of months into the past.
-- If the current day of the month doesn\'t exist in
-- the destination month, the day of the month
-- may change. The date must be valid.
dateSubtractMonths ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to decrement
    -> Word32
    -- ^ /@nMonths@/: number of months to move
    -> m ()
dateSubtractMonths :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Word32 -> m ()
dateSubtractMonths Date
date Word32
nMonths = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date -> Word32 -> IO ()
g_date_subtract_months Ptr Date
date' Word32
nMonths
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateSubtractMonthsMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.OverloadedMethod DateSubtractMonthsMethodInfo Date signature where
    overloadedMethod = dateSubtractMonths

instance O.OverloadedMethodInfo DateSubtractMonthsMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateSubtractMonths",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateSubtractMonths"
        })


#endif

-- method Date::subtract_years
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to decrement"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_years"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of years to move"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_subtract_years" g_date_subtract_years :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Word32 ->                               -- n_years : TBasicType TUInt
    IO ()

-- | Moves a date some number of years into the past.
-- If the current day doesn\'t exist in the destination
-- year (i.e. it\'s February 29 and you move to a non-leap-year)
-- then the day is changed to February 29. The date
-- must be valid.
dateSubtractYears ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to decrement
    -> Word32
    -- ^ /@nYears@/: number of years to move
    -> m ()
dateSubtractYears :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Word32 -> m ()
dateSubtractYears Date
date Word32
nYears = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date -> Word32 -> IO ()
g_date_subtract_years Ptr Date
date' Word32
nYears
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateSubtractYearsMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.OverloadedMethod DateSubtractYearsMethodInfo Date signature where
    overloadedMethod = dateSubtractYears

instance O.OverloadedMethodInfo DateSubtractYearsMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateSubtractYears",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateSubtractYears"
        })


#endif

-- method Date::to_struct_tm
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to set the struct tm from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "tm"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "struct tm to fill" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_date_to_struct_tm" g_date_to_struct_tm :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    Ptr () ->                               -- tm : TBasicType TPtr
    IO ()

-- | Fills in the date-related bits of a struct tm using the /@date@/ value.
-- Initializes the non-date parts with something safe but meaningless.
dateToStructTm ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to set the struct tm from
    -> Ptr ()
    -- ^ /@tm@/: struct tm to fill
    -> m ()
dateToStructTm :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Date -> Ptr () -> m ()
dateToStructTm Date
date Ptr ()
tm = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Ptr Date -> Ptr () -> IO ()
g_date_to_struct_tm Ptr Date
date' Ptr ()
tm
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DateToStructTmMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.OverloadedMethod DateToStructTmMethodInfo Date signature where
    overloadedMethod = dateToStructTm

instance O.OverloadedMethodInfo DateToStructTmMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateToStructTm",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateToStructTm"
        })


#endif

-- method Date::valid
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDate to check" , 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_date_valid" g_date_valid :: 
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO CInt

-- | Returns 'P.True' if the t'GI.GLib.Structs.Date.Date' represents an existing day. The date must not
-- contain garbage; it should have been initialized with 'GI.GLib.Structs.Date.dateClear'
-- if it wasn\'t allocated by one of the 'GI.GLib.Structs.Date.dateNew' variants.
dateValid ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Date
    -- ^ /@date@/: a t'GI.GLib.Structs.Date.Date' to check
    -> m Bool
    -- ^ __Returns:__ Whether the date is valid
dateValid :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Date -> m Bool
dateValid Date
date = 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 Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    CInt
result <- Ptr Date -> IO CInt
g_date_valid Ptr Date
date'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DateValidMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod DateValidMethodInfo Date signature where
    overloadedMethod = dateValid

instance O.OverloadedMethodInfo DateValidMethodInfo Date where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Date.dateValid",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Date.html#v:dateValid"
        })


#endif

-- method Date::get_days_in_month
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "month"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DateMonth" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "month" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "year"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "year" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt8)
-- throws : False
-- Skip return : False

foreign import ccall "g_date_get_days_in_month" g_date_get_days_in_month :: 
    CUInt ->                                -- month : TInterface (Name {namespace = "GLib", name = "DateMonth"})
    Word16 ->                               -- year : TBasicType TUInt16
    IO Word8

-- | Returns the number of days in a month, taking leap
-- years into account.
dateGetDaysInMonth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.Enums.DateMonth
    -- ^ /@month@/: month
    -> Word16
    -- ^ /@year@/: year
    -> m Word8
    -- ^ __Returns:__ number of days in /@month@/ during the /@year@/
dateGetDaysInMonth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DateMonth -> Word16 -> m Word8
dateGetDaysInMonth DateMonth
month Word16
year = IO Word8 -> m Word8
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word8 -> m Word8) -> IO Word8 -> m Word8
forall a b. (a -> b) -> a -> b
$ do
    let month' :: CUInt
month' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (DateMonth -> Int) -> DateMonth -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DateMonth -> Int
forall a. Enum a => a -> Int
fromEnum) DateMonth
month
    Word8
result <- CUInt -> Word16 -> IO Word8
g_date_get_days_in_month CUInt
month' Word16
year
    Word8 -> IO Word8
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
result

#if defined(ENABLE_OVERLOADING)
#endif

-- method Date::get_monday_weeks_in_year
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "year"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a year" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt8)
-- throws : False
-- Skip return : False

foreign import ccall "g_date_get_monday_weeks_in_year" g_date_get_monday_weeks_in_year :: 
    Word16 ->                               -- year : TBasicType TUInt16
    IO Word8

-- | Returns the number of weeks in the year, where weeks
-- are taken to start on Monday. Will be 52 or 53. The
-- date must be valid. (Years always have 52 7-day periods,
-- plus 1 or 2 extra days depending on whether it\'s a leap
-- year. This function is basically telling you how many
-- Mondays are in the year, i.e. there are 53 Mondays if
-- one of the extra days happens to be a Monday.)
dateGetMondayWeeksInYear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word16
    -- ^ /@year@/: a year
    -> m Word8
    -- ^ __Returns:__ number of Mondays in the year
dateGetMondayWeeksInYear :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Word16 -> m Word8
dateGetMondayWeeksInYear Word16
year = IO Word8 -> m Word8
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word8 -> m Word8) -> IO Word8 -> m Word8
forall a b. (a -> b) -> a -> b
$ do
    Word8
result <- Word16 -> IO Word8
g_date_get_monday_weeks_in_year Word16
year
    Word8 -> IO Word8
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
result

#if defined(ENABLE_OVERLOADING)
#endif

-- method Date::get_sunday_weeks_in_year
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "year"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "year to count weeks in"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt8)
-- throws : False
-- Skip return : False

foreign import ccall "g_date_get_sunday_weeks_in_year" g_date_get_sunday_weeks_in_year :: 
    Word16 ->                               -- year : TBasicType TUInt16
    IO Word8

-- | Returns the number of weeks in the year, where weeks
-- are taken to start on Sunday. Will be 52 or 53. The
-- date must be valid. (Years always have 52 7-day periods,
-- plus 1 or 2 extra days depending on whether it\'s a leap
-- year. This function is basically telling you how many
-- Sundays are in the year, i.e. there are 53 Sundays if
-- one of the extra days happens to be a Sunday.)
dateGetSundayWeeksInYear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word16
    -- ^ /@year@/: year to count weeks in
    -> m Word8
    -- ^ __Returns:__ the number of weeks in /@year@/
dateGetSundayWeeksInYear :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Word16 -> m Word8
dateGetSundayWeeksInYear Word16
year = IO Word8 -> m Word8
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word8 -> m Word8) -> IO Word8 -> m Word8
forall a b. (a -> b) -> a -> b
$ do
    Word8
result <- Word16 -> IO Word8
g_date_get_sunday_weeks_in_year Word16
year
    Word8 -> IO Word8
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
result

#if defined(ENABLE_OVERLOADING)
#endif

-- method Date::is_leap_year
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "year"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "year to check" , 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_date_is_leap_year" g_date_is_leap_year :: 
    Word16 ->                               -- year : TBasicType TUInt16
    IO CInt

-- | Returns 'P.True' if the year is a leap year.
-- 
-- For the purposes of this function, leap year is every year
-- divisible by 4 unless that year is divisible by 100. If it
-- is divisible by 100 it would be a leap year only if that year
-- is also divisible by 400.
dateIsLeapYear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word16
    -- ^ /@year@/: year to check
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the year is a leap year
dateIsLeapYear :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Word16 -> m Bool
dateIsLeapYear Word16
year = 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
    CInt
result <- Word16 -> IO CInt
g_date_is_leap_year Word16
year
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Date::strftime
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "s"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "destination buffer" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "slen"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "buffer size" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "format"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "format string" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "date"
--           , argType = TInterface Name { namespace = "GLib" , name = "Date" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "valid #GDate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "g_date_strftime" g_date_strftime :: 
    CString ->                              -- s : TBasicType TUTF8
    Word64 ->                               -- slen : TBasicType TUInt64
    CString ->                              -- format : TBasicType TUTF8
    Ptr Date ->                             -- date : TInterface (Name {namespace = "GLib", name = "Date"})
    IO Word64

-- | Generates a printed representation of the date, in a
-- [locale][setlocale]-specific way.
-- Works just like the platform\'s C library @/strftime()/@ function,
-- but only accepts date-related formats; time-related formats
-- give undefined results. Date must be valid. Unlike @/strftime()/@
-- (which uses the locale encoding), works on a UTF-8 format
-- string and stores a UTF-8 result.
-- 
-- This function does not provide any conversion specifiers in
-- addition to those implemented by the platform\'s C library.
-- For example, don\'t expect that using 'GI.GLib.Functions.dateStrftime' would
-- make the %F provided by the C99 @/strftime()/@ work on Windows
-- where the C library only complies to C89.
dateStrftime ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@s@/: destination buffer
    -> Word64
    -- ^ /@slen@/: buffer size
    -> T.Text
    -- ^ /@format@/: format string
    -> Date
    -- ^ /@date@/: valid t'GI.GLib.Structs.Date.Date'
    -> m Word64
    -- ^ __Returns:__ number of characters written to the buffer, or 0 the buffer was too small
dateStrftime :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Word64 -> Text -> Date -> m Word64
dateStrftime Text
s Word64
slen Text
format Date
date = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    CString
s' <- Text -> IO CString
textToCString Text
s
    CString
format' <- Text -> IO CString
textToCString Text
format
    Ptr Date
date' <- Date -> IO (Ptr Date)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Date
date
    Word64
result <- CString -> Word64 -> CString -> Ptr Date -> IO Word64
g_date_strftime CString
s' Word64
slen CString
format' Ptr Date
date'
    Date -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Date
date
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
s'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
format'
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
#endif

-- method Date::valid_day
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "day"
--           , argType = TBasicType TUInt8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "day to check" , 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_date_valid_day" g_date_valid_day :: 
    Word8 ->                                -- day : TBasicType TUInt8
    IO CInt

-- | Returns 'P.True' if the day of the month is valid (a day is valid if it\'s
-- between 1 and 31 inclusive).
dateValidDay ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word8
    -- ^ /@day@/: day to check
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the day is valid
dateValidDay :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Word8 -> m Bool
dateValidDay Word8
day = 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
    CInt
result <- Word8 -> IO CInt
g_date_valid_day Word8
day
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Date::valid_dmy
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "day"
--           , argType = TBasicType TUInt8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "day" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "month"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DateMonth" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "month" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "year"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "year" , 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_date_valid_dmy" g_date_valid_dmy :: 
    Word8 ->                                -- day : TBasicType TUInt8
    CUInt ->                                -- month : TInterface (Name {namespace = "GLib", name = "DateMonth"})
    Word16 ->                               -- year : TBasicType TUInt16
    IO CInt

-- | Returns 'P.True' if the day-month-year triplet forms a valid, existing day
-- in the range of days t'GI.GLib.Structs.Date.Date' understands (Year 1 or later, no more than
-- a few thousand years in the future).
dateValidDmy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word8
    -- ^ /@day@/: day
    -> GLib.Enums.DateMonth
    -- ^ /@month@/: month
    -> Word16
    -- ^ /@year@/: year
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the date is a valid one
dateValidDmy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Word8 -> DateMonth -> Word16 -> m Bool
dateValidDmy Word8
day DateMonth
month Word16
year = 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
    let month' :: CUInt
month' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (DateMonth -> Int) -> DateMonth -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DateMonth -> Int
forall a. Enum a => a -> Int
fromEnum) DateMonth
month
    CInt
result <- Word8 -> CUInt -> Word16 -> IO CInt
g_date_valid_dmy Word8
day CUInt
month' Word16
year
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Date::valid_julian
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "julian_date"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Julian day to check"
--                 , 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_date_valid_julian" g_date_valid_julian :: 
    Word32 ->                               -- julian_date : TBasicType TUInt32
    IO CInt

-- | Returns 'P.True' if the Julian day is valid. Anything greater than zero
-- is basically a valid Julian, though there is a 32-bit limit.
dateValidJulian ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word32
    -- ^ /@julianDate@/: Julian day to check
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the Julian day is valid
dateValidJulian :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Word32 -> m Bool
dateValidJulian Word32
julianDate = 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
    CInt
result <- Word32 -> IO CInt
g_date_valid_julian Word32
julianDate
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Date::valid_month
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "month"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DateMonth" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "month" , 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_date_valid_month" g_date_valid_month :: 
    CUInt ->                                -- month : TInterface (Name {namespace = "GLib", name = "DateMonth"})
    IO CInt

-- | Returns 'P.True' if the month value is valid. The 12 t'GI.GLib.Enums.DateMonth'
-- enumeration values are the only valid months.
dateValidMonth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.Enums.DateMonth
    -- ^ /@month@/: month
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the month is valid
dateValidMonth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DateMonth -> m Bool
dateValidMonth DateMonth
month = 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
    let month' :: CUInt
month' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (DateMonth -> Int) -> DateMonth -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DateMonth -> Int
forall a. Enum a => a -> Int
fromEnum) DateMonth
month
    CInt
result <- CUInt -> IO CInt
g_date_valid_month CUInt
month'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Date::valid_weekday
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "weekday"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DateWeekday" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "weekday" , 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_date_valid_weekday" g_date_valid_weekday :: 
    CUInt ->                                -- weekday : TInterface (Name {namespace = "GLib", name = "DateWeekday"})
    IO CInt

-- | Returns 'P.True' if the weekday is valid. The seven t'GI.GLib.Enums.DateWeekday' enumeration
-- values are the only valid weekdays.
dateValidWeekday ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.Enums.DateWeekday
    -- ^ /@weekday@/: weekday
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the weekday is valid
dateValidWeekday :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DateWeekday -> m Bool
dateValidWeekday DateWeekday
weekday = 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
    let weekday' :: CUInt
weekday' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (DateWeekday -> Int) -> DateWeekday -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DateWeekday -> Int
forall a. Enum a => a -> Int
fromEnum) DateWeekday
weekday
    CInt
result <- CUInt -> IO CInt
g_date_valid_weekday CUInt
weekday'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Date::valid_year
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "year"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "year" , 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_date_valid_year" g_date_valid_year :: 
    Word16 ->                               -- year : TBasicType TUInt16
    IO CInt

-- | Returns 'P.True' if the year is valid. Any year greater than 0 is valid,
-- though there is a 16-bit limit to what t'GI.GLib.Structs.Date.Date' will understand.
dateValidYear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word16
    -- ^ /@year@/: year
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the year is valid
dateValidYear :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Word16 -> m Bool
dateValidYear Word16
year = 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
    CInt
result <- Word16 -> IO CInt
g_date_valid_year Word16
year
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveDateMethod (t :: Symbol) (o :: *) :: * where
    ResolveDateMethod "addDays" o = DateAddDaysMethodInfo
    ResolveDateMethod "addMonths" o = DateAddMonthsMethodInfo
    ResolveDateMethod "addYears" o = DateAddYearsMethodInfo
    ResolveDateMethod "clamp" o = DateClampMethodInfo
    ResolveDateMethod "clear" o = DateClearMethodInfo
    ResolveDateMethod "compare" o = DateCompareMethodInfo
    ResolveDateMethod "copy" o = DateCopyMethodInfo
    ResolveDateMethod "daysBetween" o = DateDaysBetweenMethodInfo
    ResolveDateMethod "free" o = DateFreeMethodInfo
    ResolveDateMethod "isFirstOfMonth" o = DateIsFirstOfMonthMethodInfo
    ResolveDateMethod "isLastOfMonth" o = DateIsLastOfMonthMethodInfo
    ResolveDateMethod "order" o = DateOrderMethodInfo
    ResolveDateMethod "subtractDays" o = DateSubtractDaysMethodInfo
    ResolveDateMethod "subtractMonths" o = DateSubtractMonthsMethodInfo
    ResolveDateMethod "subtractYears" o = DateSubtractYearsMethodInfo
    ResolveDateMethod "toStructTm" o = DateToStructTmMethodInfo
    ResolveDateMethod "valid" o = DateValidMethodInfo
    ResolveDateMethod "getDay" o = DateGetDayMethodInfo
    ResolveDateMethod "getDayOfYear" o = DateGetDayOfYearMethodInfo
    ResolveDateMethod "getIso8601WeekOfYear" o = DateGetIso8601WeekOfYearMethodInfo
    ResolveDateMethod "getJulian" o = DateGetJulianMethodInfo
    ResolveDateMethod "getMondayWeekOfYear" o = DateGetMondayWeekOfYearMethodInfo
    ResolveDateMethod "getMonth" o = DateGetMonthMethodInfo
    ResolveDateMethod "getSundayWeekOfYear" o = DateGetSundayWeekOfYearMethodInfo
    ResolveDateMethod "getWeekday" o = DateGetWeekdayMethodInfo
    ResolveDateMethod "getYear" o = DateGetYearMethodInfo
    ResolveDateMethod "setDay" o = DateSetDayMethodInfo
    ResolveDateMethod "setDmy" o = DateSetDmyMethodInfo
    ResolveDateMethod "setJulian" o = DateSetJulianMethodInfo
    ResolveDateMethod "setMonth" o = DateSetMonthMethodInfo
    ResolveDateMethod "setParse" o = DateSetParseMethodInfo
    ResolveDateMethod "setTime" o = DateSetTimeMethodInfo
    ResolveDateMethod "setTimeT" o = DateSetTimeTMethodInfo
    ResolveDateMethod "setTimeVal" o = DateSetTimeValMethodInfo
    ResolveDateMethod "setYear" o = DateSetYearMethodInfo
    ResolveDateMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDateMethod t Date, O.OverloadedMethod info Date p) => OL.IsLabel t (Date -> 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 ~ ResolveDateMethod t Date, O.OverloadedMethod info Date p, R.HasField t Date p) => R.HasField t Date p where
    getField = O.overloadedMethod @info

#endif

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

#endif