{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GLib.Structs.Date
(
Date(..) ,
newZeroDate ,
noDate ,
#if defined(ENABLE_OVERLOADING)
ResolveDateMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DateAddDaysMethodInfo ,
#endif
dateAddDays ,
#if defined(ENABLE_OVERLOADING)
DateAddMonthsMethodInfo ,
#endif
dateAddMonths ,
#if defined(ENABLE_OVERLOADING)
DateAddYearsMethodInfo ,
#endif
dateAddYears ,
#if defined(ENABLE_OVERLOADING)
DateClampMethodInfo ,
#endif
dateClamp ,
#if defined(ENABLE_OVERLOADING)
DateClearMethodInfo ,
#endif
dateClear ,
#if defined(ENABLE_OVERLOADING)
DateCompareMethodInfo ,
#endif
dateCompare ,
#if defined(ENABLE_OVERLOADING)
DateCopyMethodInfo ,
#endif
dateCopy ,
#if defined(ENABLE_OVERLOADING)
DateDaysBetweenMethodInfo ,
#endif
dateDaysBetween ,
#if defined(ENABLE_OVERLOADING)
DateFreeMethodInfo ,
#endif
dateFree ,
#if defined(ENABLE_OVERLOADING)
DateGetDayMethodInfo ,
#endif
dateGetDay ,
#if defined(ENABLE_OVERLOADING)
DateGetDayOfYearMethodInfo ,
#endif
dateGetDayOfYear ,
dateGetDaysInMonth ,
#if defined(ENABLE_OVERLOADING)
DateGetIso8601WeekOfYearMethodInfo ,
#endif
dateGetIso8601WeekOfYear ,
#if defined(ENABLE_OVERLOADING)
DateGetJulianMethodInfo ,
#endif
dateGetJulian ,
#if defined(ENABLE_OVERLOADING)
DateGetMondayWeekOfYearMethodInfo ,
#endif
dateGetMondayWeekOfYear ,
dateGetMondayWeeksInYear ,
#if defined(ENABLE_OVERLOADING)
DateGetMonthMethodInfo ,
#endif
dateGetMonth ,
#if defined(ENABLE_OVERLOADING)
DateGetSundayWeekOfYearMethodInfo ,
#endif
dateGetSundayWeekOfYear ,
dateGetSundayWeeksInYear ,
#if defined(ENABLE_OVERLOADING)
DateGetWeekdayMethodInfo ,
#endif
dateGetWeekday ,
#if defined(ENABLE_OVERLOADING)
DateGetYearMethodInfo ,
#endif
dateGetYear ,
#if defined(ENABLE_OVERLOADING)
DateIsFirstOfMonthMethodInfo ,
#endif
dateIsFirstOfMonth ,
#if defined(ENABLE_OVERLOADING)
DateIsLastOfMonthMethodInfo ,
#endif
dateIsLastOfMonth ,
dateIsLeapYear ,
dateNew ,
dateNewDmy ,
dateNewJulian ,
#if defined(ENABLE_OVERLOADING)
DateOrderMethodInfo ,
#endif
dateOrder ,
#if defined(ENABLE_OVERLOADING)
DateSetDayMethodInfo ,
#endif
dateSetDay ,
#if defined(ENABLE_OVERLOADING)
DateSetDmyMethodInfo ,
#endif
dateSetDmy ,
#if defined(ENABLE_OVERLOADING)
DateSetJulianMethodInfo ,
#endif
dateSetJulian ,
#if defined(ENABLE_OVERLOADING)
DateSetMonthMethodInfo ,
#endif
dateSetMonth ,
#if defined(ENABLE_OVERLOADING)
DateSetParseMethodInfo ,
#endif
dateSetParse ,
#if defined(ENABLE_OVERLOADING)
DateSetTimeMethodInfo ,
#endif
dateSetTime ,
#if defined(ENABLE_OVERLOADING)
DateSetTimeTMethodInfo ,
#endif
dateSetTimeT ,
#if defined(ENABLE_OVERLOADING)
DateSetTimeValMethodInfo ,
#endif
dateSetTimeVal ,
#if defined(ENABLE_OVERLOADING)
DateSetYearMethodInfo ,
#endif
dateSetYear ,
dateStrftime ,
#if defined(ENABLE_OVERLOADING)
DateSubtractDaysMethodInfo ,
#endif
dateSubtractDays ,
#if defined(ENABLE_OVERLOADING)
DateSubtractMonthsMethodInfo ,
#endif
dateSubtractMonths ,
#if defined(ENABLE_OVERLOADING)
DateSubtractYearsMethodInfo ,
#endif
dateSubtractYears ,
#if defined(ENABLE_OVERLOADING)
DateToStructTmMethodInfo ,
#endif
dateToStructTm ,
#if defined(ENABLE_OVERLOADING)
DateValidMethodInfo ,
#endif
dateValid ,
dateValidDay ,
dateValidDmy ,
dateValidJulian ,
dateValidMonth ,
dateValidWeekday ,
dateValidYear ,
#if defined(ENABLE_OVERLOADING)
date_day ,
#endif
getDateDay ,
setDateDay ,
#if defined(ENABLE_OVERLOADING)
date_dmy ,
#endif
getDateDmy ,
setDateDmy ,
#if defined(ENABLE_OVERLOADING)
date_julian ,
#endif
getDateJulian ,
setDateJulian ,
#if defined(ENABLE_OVERLOADING)
date_julianDays ,
#endif
getDateJulianDays ,
setDateJulianDays ,
#if defined(ENABLE_OVERLOADING)
date_month ,
#endif
getDateMonth ,
setDateMonth ,
#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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified 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 {-# SOURCE #-} qualified GI.GLib.Enums as GLib.Enums
import {-# SOURCE #-} qualified GI.GLib.Structs.TimeVal as GLib.TimeVal
newtype Date = Date (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)
foreign import ccall "g_date_get_type" c_g_date_get_type ::
IO GType
instance BoxedObject Date where
boxedType :: Date -> IO GType
boxedType _ = IO GType
c_g_date_get_type
instance B.GValue.IsGValue Date where
toGValue :: Date -> IO GValue
toGValue o :: Date
o = do
GType
gtype <- IO GType
c_g_date_get_type
Date -> (Ptr Date -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Date
o (GType -> (GValue -> Ptr Date -> IO ()) -> Ptr Date -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Date -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
fromGValue :: GValue -> IO Date
fromGValue gv :: GValue
gv = do
Ptr Date
ptr <- GValue -> IO (Ptr Date)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr Date)
(ManagedPtr Date -> Date) -> Ptr Date -> IO Date
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Date -> Date
Date Ptr Date
ptr
newZeroDate :: MonadIO m => m Date
newZeroDate :: 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. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 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, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Date -> Date
Date
instance tag ~ 'AttrSet => Constructible Date tag where
new :: (ManagedPtr Date -> Date) -> [AttrOp Date tag] -> m Date
new _ attrs :: [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
noDate :: Maybe Date
noDate :: Maybe Date
noDate = Maybe Date
forall a. Maybe a
Nothing
getDateJulianDays :: MonadIO m => Date -> m Word32
getDateJulianDays :: Date -> m Word32
getDateJulianDays s :: 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 :: 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` 0) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setDateJulianDays :: MonadIO m => Date -> Word32 -> m ()
setDateJulianDays :: Date -> Word32 -> m ()
setDateJulianDays s :: Date
s val :: 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 :: 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` 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
date_julianDays :: AttrLabelProxy "julianDays"
date_julianDays = AttrLabelProxy
#endif
getDateJulian :: MonadIO m => Date -> m Word32
getDateJulian :: Date -> m Word32
getDateJulian s :: 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 :: 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` 4) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setDateJulian :: MonadIO m => Date -> Word32 -> m ()
setDateJulian :: Date -> Word32 -> m ()
setDateJulian s :: Date
s val :: 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 :: 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` 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
date_julian :: AttrLabelProxy "julian"
date_julian = AttrLabelProxy
#endif
getDateDmy :: MonadIO m => Date -> m Word32
getDateDmy :: Date -> m Word32
getDateDmy s :: 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 :: 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` 8) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setDateDmy :: MonadIO m => Date -> Word32 -> m ()
setDateDmy :: Date -> Word32 -> m ()
setDateDmy s :: Date
s val :: 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 :: 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` 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
date_dmy :: AttrLabelProxy "dmy"
date_dmy = AttrLabelProxy
#endif
getDateDay :: MonadIO m => Date -> m Word32
getDateDay :: Date -> m Word32
getDateDay s :: 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 :: 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` 12) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setDateDay :: MonadIO m => Date -> Word32 -> m ()
setDateDay :: Date -> Word32 -> m ()
setDateDay s :: Date
s val :: 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 :: 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` 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
date_day :: AttrLabelProxy "day"
date_day = AttrLabelProxy
#endif
getDateMonth :: MonadIO m => Date -> m Word32
getDateMonth :: Date -> m Word32
getDateMonth s :: 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 :: 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` 16) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setDateMonth :: MonadIO m => Date -> Word32 -> m ()
setDateMonth :: Date -> Word32 -> m ()
setDateMonth s :: Date
s val :: 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 :: 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` 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
date_month :: AttrLabelProxy "month"
date_month = AttrLabelProxy
#endif
getDateYear :: MonadIO m => Date -> m Word32
getDateYear :: Date -> m Word32
getDateYear s :: 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 :: 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` 20) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setDateYear :: MonadIO m => Date -> Word32 -> m ()
setDateYear :: Date -> Word32 -> m ()
setDateYear s :: Date
s val :: 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 :: 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` 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
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
foreign import ccall "g_date_new" g_date_new ::
IO (Ptr Date)
dateNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m Date
dateNew :: 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 "dateNew" Ptr Date
result
Date
result' <- ((ManagedPtr Date -> Date) -> Ptr Date -> IO Date
forall a.
(HasCallStack, BoxedObject 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
foreign import ccall "g_date_new_dmy" g_date_new_dmy ::
Word8 ->
CUInt ->
Word16 ->
IO (Ptr Date)
dateNewDmy ::
(B.CallStack.HasCallStack, MonadIO m) =>
Word8
-> GLib.Enums.DateMonth
-> Word16
-> m Date
dateNewDmy :: Word8 -> DateMonth -> Word16 -> m Date
dateNewDmy day :: Word8
day month :: DateMonth
month year :: 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 "dateNewDmy" Ptr Date
result
Date
result' <- ((ManagedPtr Date -> Date) -> Ptr Date -> IO Date
forall a.
(HasCallStack, BoxedObject 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
foreign import ccall "g_date_new_julian" g_date_new_julian ::
Word32 ->
IO (Ptr Date)
dateNewJulian ::
(B.CallStack.HasCallStack, MonadIO m) =>
Word32
-> m Date
dateNewJulian :: Word32 -> m Date
dateNewJulian julianDay :: 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 "dateNewJulian" Ptr Date
result
Date
result' <- ((ManagedPtr Date -> Date) -> Ptr Date -> IO Date
forall a.
(HasCallStack, BoxedObject 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
foreign import ccall "g_date_add_days" g_date_add_days ::
Ptr Date ->
Word32 ->
IO ()
dateAddDays ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Word32
-> m ()
dateAddDays :: Date -> Word32 -> m ()
dateAddDays date :: Date
date nDays :: 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.MethodInfo DateAddDaysMethodInfo Date signature where
overloadedMethod = dateAddDays
#endif
foreign import ccall "g_date_add_months" g_date_add_months ::
Ptr Date ->
Word32 ->
IO ()
dateAddMonths ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Word32
-> m ()
dateAddMonths :: Date -> Word32 -> m ()
dateAddMonths date :: Date
date nMonths :: 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.MethodInfo DateAddMonthsMethodInfo Date signature where
overloadedMethod = dateAddMonths
#endif
foreign import ccall "g_date_add_years" g_date_add_years ::
Ptr Date ->
Word32 ->
IO ()
dateAddYears ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Word32
-> m ()
dateAddYears :: Date -> Word32 -> m ()
dateAddYears date :: Date
date nYears :: 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.MethodInfo DateAddYearsMethodInfo Date signature where
overloadedMethod = dateAddYears
#endif
foreign import ccall "g_date_clamp" g_date_clamp ::
Ptr Date ->
Ptr Date ->
Ptr Date ->
IO ()
dateClamp ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Date
-> Date
-> m ()
dateClamp :: Date -> Date -> Date -> m ()
dateClamp date :: Date
date minDate :: Date
minDate maxDate :: 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.MethodInfo DateClampMethodInfo Date signature where
overloadedMethod = dateClamp
#endif
foreign import ccall "g_date_clear" g_date_clear ::
Ptr Date ->
Word32 ->
IO ()
dateClear ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Word32
-> m ()
dateClear :: Date -> Word32 -> m ()
dateClear date :: Date
date nDates :: 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.MethodInfo DateClearMethodInfo Date signature where
overloadedMethod = dateClear
#endif
foreign import ccall "g_date_compare" g_date_compare ::
Ptr Date ->
Ptr Date ->
IO Int32
dateCompare ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Date
-> m Int32
dateCompare :: Date -> Date -> m Int32
dateCompare lhs :: Date
lhs rhs :: 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.MethodInfo DateCompareMethodInfo Date signature where
overloadedMethod = dateCompare
#endif
foreign import ccall "g_date_copy" g_date_copy ::
Ptr Date ->
IO (Ptr Date)
dateCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> m Date
dateCopy :: Date -> m Date
dateCopy date :: 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 "dateCopy" Ptr Date
result
Date
result' <- ((ManagedPtr Date -> Date) -> Ptr Date -> IO Date
forall a.
(HasCallStack, BoxedObject 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.MethodInfo DateCopyMethodInfo Date signature where
overloadedMethod = dateCopy
#endif
foreign import ccall "g_date_days_between" g_date_days_between ::
Ptr Date ->
Ptr Date ->
IO Int32
dateDaysBetween ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Date
-> m Int32
dateDaysBetween :: Date -> Date -> m Int32
dateDaysBetween date1 :: Date
date1 date2 :: 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.MethodInfo DateDaysBetweenMethodInfo Date signature where
overloadedMethod = dateDaysBetween
#endif
foreign import ccall "g_date_free" g_date_free ::
Ptr Date ->
IO ()
dateFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> m ()
dateFree :: Date -> m ()
dateFree date :: 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.MethodInfo DateFreeMethodInfo Date signature where
overloadedMethod = dateFree
#endif
foreign import ccall "g_date_get_day" g_date_get_day ::
Ptr Date ->
IO Word8
dateGetDay ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> m Word8
dateGetDay :: Date -> m Word8
dateGetDay date :: 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.MethodInfo DateGetDayMethodInfo Date signature where
overloadedMethod = dateGetDay
#endif
foreign import ccall "g_date_get_day_of_year" g_date_get_day_of_year ::
Ptr Date ->
IO Word32
dateGetDayOfYear ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> m Word32
dateGetDayOfYear :: Date -> m Word32
dateGetDayOfYear date :: 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.MethodInfo DateGetDayOfYearMethodInfo Date signature where
overloadedMethod = dateGetDayOfYear
#endif
foreign import ccall "g_date_get_iso8601_week_of_year" g_date_get_iso8601_week_of_year ::
Ptr Date ->
IO Word32
dateGetIso8601WeekOfYear ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> m Word32
dateGetIso8601WeekOfYear :: Date -> m Word32
dateGetIso8601WeekOfYear date :: 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.MethodInfo DateGetIso8601WeekOfYearMethodInfo Date signature where
overloadedMethod = dateGetIso8601WeekOfYear
#endif
foreign import ccall "g_date_get_julian" g_date_get_julian ::
Ptr Date ->
IO Word32
dateGetJulian ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> m Word32
dateGetJulian :: Date -> m Word32
dateGetJulian date :: 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.MethodInfo DateGetJulianMethodInfo Date signature where
overloadedMethod = dateGetJulian
#endif
foreign import ccall "g_date_get_monday_week_of_year" g_date_get_monday_week_of_year ::
Ptr Date ->
IO Word32
dateGetMondayWeekOfYear ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> m Word32
dateGetMondayWeekOfYear :: Date -> m Word32
dateGetMondayWeekOfYear date :: 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.MethodInfo DateGetMondayWeekOfYearMethodInfo Date signature where
overloadedMethod = dateGetMondayWeekOfYear
#endif
foreign import ccall "g_date_get_month" g_date_get_month ::
Ptr Date ->
IO CUInt
dateGetMonth ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> m GLib.Enums.DateMonth
dateGetMonth :: Date -> m DateMonth
dateGetMonth date :: 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.MethodInfo DateGetMonthMethodInfo Date signature where
overloadedMethod = dateGetMonth
#endif
foreign import ccall "g_date_get_sunday_week_of_year" g_date_get_sunday_week_of_year ::
Ptr Date ->
IO Word32
dateGetSundayWeekOfYear ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> m Word32
dateGetSundayWeekOfYear :: Date -> m Word32
dateGetSundayWeekOfYear date :: 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.MethodInfo DateGetSundayWeekOfYearMethodInfo Date signature where
overloadedMethod = dateGetSundayWeekOfYear
#endif
foreign import ccall "g_date_get_weekday" g_date_get_weekday ::
Ptr Date ->
IO CUInt
dateGetWeekday ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> m GLib.Enums.DateWeekday
dateGetWeekday :: Date -> m DateWeekday
dateGetWeekday date :: 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.MethodInfo DateGetWeekdayMethodInfo Date signature where
overloadedMethod = dateGetWeekday
#endif
foreign import ccall "g_date_get_year" g_date_get_year ::
Ptr Date ->
IO Word16
dateGetYear ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> m Word16
dateGetYear :: Date -> m Word16
dateGetYear date :: 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.MethodInfo DateGetYearMethodInfo Date signature where
overloadedMethod = dateGetYear
#endif
foreign import ccall "g_date_is_first_of_month" g_date_is_first_of_month ::
Ptr Date ->
IO CInt
dateIsFirstOfMonth ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> m Bool
dateIsFirstOfMonth :: Date -> m Bool
dateIsFirstOfMonth date :: 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
/= 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.MethodInfo DateIsFirstOfMonthMethodInfo Date signature where
overloadedMethod = dateIsFirstOfMonth
#endif
foreign import ccall "g_date_is_last_of_month" g_date_is_last_of_month ::
Ptr Date ->
IO CInt
dateIsLastOfMonth ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> m Bool
dateIsLastOfMonth :: Date -> m Bool
dateIsLastOfMonth date :: 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
/= 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.MethodInfo DateIsLastOfMonthMethodInfo Date signature where
overloadedMethod = dateIsLastOfMonth
#endif
foreign import ccall "g_date_order" g_date_order ::
Ptr Date ->
Ptr Date ->
IO ()
dateOrder ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Date
-> m ()
dateOrder :: Date -> Date -> m ()
dateOrder date1 :: Date
date1 date2 :: 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.MethodInfo DateOrderMethodInfo Date signature where
overloadedMethod = dateOrder
#endif
foreign import ccall "g_date_set_day" g_date_set_day ::
Ptr Date ->
Word8 ->
IO ()
dateSetDay ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Word8
-> m ()
dateSetDay :: Date -> Word8 -> m ()
dateSetDay date :: Date
date day :: 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.MethodInfo DateSetDayMethodInfo Date signature where
overloadedMethod = dateSetDay
#endif
foreign import ccall "g_date_set_dmy" g_date_set_dmy ::
Ptr Date ->
Word8 ->
CUInt ->
Word16 ->
IO ()
dateSetDmy ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Word8
-> GLib.Enums.DateMonth
-> Word16
-> m ()
dateSetDmy :: Date -> Word8 -> DateMonth -> Word16 -> m ()
dateSetDmy date :: Date
date day :: Word8
day month :: DateMonth
month y :: 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.MethodInfo DateSetDmyMethodInfo Date signature where
overloadedMethod = dateSetDmy
#endif
foreign import ccall "g_date_set_julian" g_date_set_julian ::
Ptr Date ->
Word32 ->
IO ()
dateSetJulian ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Word32
-> m ()
dateSetJulian :: Date -> Word32 -> m ()
dateSetJulian date :: Date
date julianDate :: 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.MethodInfo DateSetJulianMethodInfo Date signature where
overloadedMethod = dateSetJulian
#endif
foreign import ccall "g_date_set_month" g_date_set_month ::
Ptr Date ->
CUInt ->
IO ()
dateSetMonth ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> GLib.Enums.DateMonth
-> m ()
dateSetMonth :: Date -> DateMonth -> m ()
dateSetMonth date :: Date
date month :: 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.MethodInfo DateSetMonthMethodInfo Date signature where
overloadedMethod = dateSetMonth
#endif
foreign import ccall "g_date_set_parse" g_date_set_parse ::
Ptr Date ->
CString ->
IO ()
dateSetParse ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> T.Text
-> m ()
dateSetParse :: Date -> Text -> m ()
dateSetParse date :: Date
date str :: 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.MethodInfo DateSetParseMethodInfo Date signature where
overloadedMethod = dateSetParse
#endif
foreign import ccall "g_date_set_time" g_date_set_time ::
Ptr Date ->
Int32 ->
IO ()
{-# DEPRECATED dateSetTime ["(Since version 2.10)","Use 'GI.GLib.Structs.Date.dateSetTimeT' instead."] #-}
dateSetTime ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Int32
-> m ()
dateSetTime :: Date -> Int32 -> m ()
dateSetTime date :: Date
date time_ :: 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.MethodInfo DateSetTimeMethodInfo Date signature where
overloadedMethod = dateSetTime
#endif
foreign import ccall "g_date_set_time_t" g_date_set_time_t ::
Ptr Date ->
CLong ->
IO ()
dateSetTimeT ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> CLong
-> m ()
dateSetTimeT :: Date -> CLong -> m ()
dateSetTimeT date :: Date
date timet :: 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.MethodInfo DateSetTimeTMethodInfo Date signature where
overloadedMethod = dateSetTimeT
#endif
foreign import ccall "g_date_set_time_val" g_date_set_time_val ::
Ptr Date ->
Ptr GLib.TimeVal.TimeVal ->
IO ()
dateSetTimeVal ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> GLib.TimeVal.TimeVal
-> m ()
dateSetTimeVal :: Date -> TimeVal -> m ()
dateSetTimeVal date :: Date
date timeval :: 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.MethodInfo DateSetTimeValMethodInfo Date signature where
overloadedMethod = dateSetTimeVal
#endif
foreign import ccall "g_date_set_year" g_date_set_year ::
Ptr Date ->
Word16 ->
IO ()
dateSetYear ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Word16
-> m ()
dateSetYear :: Date -> Word16 -> m ()
dateSetYear date :: Date
date year :: 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.MethodInfo DateSetYearMethodInfo Date signature where
overloadedMethod = dateSetYear
#endif
foreign import ccall "g_date_subtract_days" g_date_subtract_days ::
Ptr Date ->
Word32 ->
IO ()
dateSubtractDays ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Word32
-> m ()
dateSubtractDays :: Date -> Word32 -> m ()
dateSubtractDays date :: Date
date nDays :: 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.MethodInfo DateSubtractDaysMethodInfo Date signature where
overloadedMethod = dateSubtractDays
#endif
foreign import ccall "g_date_subtract_months" g_date_subtract_months ::
Ptr Date ->
Word32 ->
IO ()
dateSubtractMonths ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Word32
-> m ()
dateSubtractMonths :: Date -> Word32 -> m ()
dateSubtractMonths date :: Date
date nMonths :: 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.MethodInfo DateSubtractMonthsMethodInfo Date signature where
overloadedMethod = dateSubtractMonths
#endif
foreign import ccall "g_date_subtract_years" g_date_subtract_years ::
Ptr Date ->
Word32 ->
IO ()
dateSubtractYears ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Word32
-> m ()
dateSubtractYears :: Date -> Word32 -> m ()
dateSubtractYears date :: Date
date nYears :: 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.MethodInfo DateSubtractYearsMethodInfo Date signature where
overloadedMethod = dateSubtractYears
#endif
foreign import ccall "g_date_to_struct_tm" g_date_to_struct_tm ::
Ptr Date ->
Ptr () ->
IO ()
dateToStructTm ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> Ptr ()
-> m ()
dateToStructTm :: Date -> Ptr () -> m ()
dateToStructTm date :: Date
date tm :: 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.MethodInfo DateToStructTmMethodInfo Date signature where
overloadedMethod = dateToStructTm
#endif
foreign import ccall "g_date_valid" g_date_valid ::
Ptr Date ->
IO CInt
dateValid ::
(B.CallStack.HasCallStack, MonadIO m) =>
Date
-> m Bool
dateValid :: Date -> m Bool
dateValid date :: 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
/= 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.MethodInfo DateValidMethodInfo Date signature where
overloadedMethod = dateValid
#endif
foreign import ccall "g_date_get_days_in_month" g_date_get_days_in_month ::
CUInt ->
Word16 ->
IO Word8
dateGetDaysInMonth ::
(B.CallStack.HasCallStack, MonadIO m) =>
GLib.Enums.DateMonth
-> Word16
-> m Word8
dateGetDaysInMonth :: DateMonth -> Word16 -> m Word8
dateGetDaysInMonth month :: DateMonth
month year :: 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
foreign import ccall "g_date_get_monday_weeks_in_year" g_date_get_monday_weeks_in_year ::
Word16 ->
IO Word8
dateGetMondayWeeksInYear ::
(B.CallStack.HasCallStack, MonadIO m) =>
Word16
-> m Word8
dateGetMondayWeeksInYear :: Word16 -> m Word8
dateGetMondayWeeksInYear year :: 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
foreign import ccall "g_date_get_sunday_weeks_in_year" g_date_get_sunday_weeks_in_year ::
Word16 ->
IO Word8
dateGetSundayWeeksInYear ::
(B.CallStack.HasCallStack, MonadIO m) =>
Word16
-> m Word8
dateGetSundayWeeksInYear :: Word16 -> m Word8
dateGetSundayWeeksInYear year :: 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
foreign import ccall "g_date_is_leap_year" g_date_is_leap_year ::
Word16 ->
IO CInt
dateIsLeapYear ::
(B.CallStack.HasCallStack, MonadIO m) =>
Word16
-> m Bool
dateIsLeapYear :: Word16 -> m Bool
dateIsLeapYear year :: 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
/= 0) CInt
result
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_date_strftime" g_date_strftime ::
CString ->
Word64 ->
CString ->
Ptr Date ->
IO Word64
dateStrftime ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> Word64
-> T.Text
-> Date
-> m Word64
dateStrftime :: Text -> Word64 -> Text -> Date -> m Word64
dateStrftime s :: Text
s slen :: Word64
slen format :: Text
format date :: 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
foreign import ccall "g_date_valid_day" g_date_valid_day ::
Word8 ->
IO CInt
dateValidDay ::
(B.CallStack.HasCallStack, MonadIO m) =>
Word8
-> m Bool
dateValidDay :: Word8 -> m Bool
dateValidDay day :: 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
/= 0) CInt
result
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_date_valid_dmy" g_date_valid_dmy ::
Word8 ->
CUInt ->
Word16 ->
IO CInt
dateValidDmy ::
(B.CallStack.HasCallStack, MonadIO m) =>
Word8
-> GLib.Enums.DateMonth
-> Word16
-> m Bool
dateValidDmy :: Word8 -> DateMonth -> Word16 -> m Bool
dateValidDmy day :: Word8
day month :: DateMonth
month year :: 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
/= 0) CInt
result
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_date_valid_julian" g_date_valid_julian ::
Word32 ->
IO CInt
dateValidJulian ::
(B.CallStack.HasCallStack, MonadIO m) =>
Word32
-> m Bool
dateValidJulian :: Word32 -> m Bool
dateValidJulian julianDate :: 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
/= 0) CInt
result
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_date_valid_month" g_date_valid_month ::
CUInt ->
IO CInt
dateValidMonth ::
(B.CallStack.HasCallStack, MonadIO m) =>
GLib.Enums.DateMonth
-> m Bool
dateValidMonth :: DateMonth -> m Bool
dateValidMonth month :: 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
/= 0) CInt
result
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_date_valid_weekday" g_date_valid_weekday ::
CUInt ->
IO CInt
dateValidWeekday ::
(B.CallStack.HasCallStack, MonadIO m) =>
GLib.Enums.DateWeekday
-> m Bool
dateValidWeekday :: DateWeekday -> m Bool
dateValidWeekday weekday :: 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
/= 0) CInt
result
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_date_valid_year" g_date_valid_year ::
Word16 ->
IO CInt
dateValidYear ::
(B.CallStack.HasCallStack, MonadIO m) =>
Word16
-> m Bool
dateValidYear :: Word16 -> m Bool
dateValidYear year :: 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
/= 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.MethodInfo 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
#endif