{-# LINE 1 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
module System.Directory.Internal.C_utimensat where
{-# LINE 4 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
{-# LINE 5 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
{-# LINE 7 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
{-# LINE 8 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
{-# LINE 10 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
{-# LINE 11 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
{-# LINE 13 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
import Prelude ()
import System.Directory.Internal.Prelude
import Data.Time.Clock.POSIX (POSIXTime)
data CTimeSpec = CTimeSpec EpochTime CLong
instance Storable CTimeSpec where
sizeOf :: CTimeSpec -> Int
sizeOf CTimeSpec
_ = (Int
16)
{-# LINE 22 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
alignment :: CTimeSpec -> Int
alignment CTimeSpec
_ = (Int
8)
{-# LINE 24 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
poke p (CTimeSpec sec nsec) = do
((\hsc_ptr -> pokeByteOff hsc_ptr 0)) p sec
{-# LINE 26 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p nsec
{-# LINE 27 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
peek p = do
sec <- (\hsc_ptr -> peekByteOff hsc_ptr 0) p
{-# LINE 29 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
nsec <- (\hsc_ptr -> peekByteOff hsc_ptr 8) p
{-# LINE 30 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
return (CTimeSpec sec nsec)
c_AT_FDCWD :: CInt
c_AT_FDCWD :: CInt
c_AT_FDCWD = (-CInt
100)
{-# LINE 34 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
utimeOmit :: CTimeSpec
utimeOmit :: CTimeSpec
utimeOmit = EpochTime -> CLong -> CTimeSpec
CTimeSpec (Int64 -> EpochTime
CTime Int64
0) (CLong
1073741822)
{-# LINE 37 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}
toCTimeSpec :: POSIXTime -> CTimeSpec
toCTimeSpec :: POSIXTime -> CTimeSpec
toCTimeSpec POSIXTime
t = EpochTime -> CLong -> CTimeSpec
CTimeSpec (Int64 -> EpochTime
CTime Int64
sec) (Rational -> CLong
forall a b. (RealFrac a, Integral b) => a -> b
External instance of the constraint type Integral CLong
External instance of the constraint type forall a. Integral a => RealFrac (Ratio a)
External instance of the constraint type Integral Integer
truncate (Rational -> CLong) -> Rational -> CLong
forall a b. (a -> b) -> a -> b
$ Rational
10 Rational -> Int -> Rational
forall a b. (Num a, Integral b) => a -> b -> a
External instance of the constraint type Integral Int
External instance of the constraint type forall a. Integral a => Num (Ratio a)
External instance of the constraint type Integral Integer
^ (Int
9 :: Int) Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
External instance of the constraint type forall a. Integral a => Num (Ratio a)
External instance of the constraint type Integral Integer
* Rational
frac)
where
(Int64
sec, Rational
frac) = if Rational
frac' Rational -> Rational -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type forall a. Integral a => Ord (Ratio a)
External instance of the constraint type Integral Integer
< Rational
0 then (Int64
sec' Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int64
- Int64
1, Rational
frac' Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
External instance of the constraint type forall a. Integral a => Num (Ratio a)
External instance of the constraint type Integral Integer
+ Rational
1) else (Int64
sec', Rational
frac')
(Int64
sec', Rational
frac') = Rational -> (Int64, Rational)
forall a b. (RealFrac a, Integral b) => a -> (b, a)
External instance of the constraint type Integral Int64
External instance of the constraint type forall a. Integral a => RealFrac (Ratio a)
External instance of the constraint type Integral Integer
properFraction (POSIXTime -> Rational
forall a. Real a => a -> Rational
External instance of the constraint type Real POSIXTime
toRational POSIXTime
t)
foreign import ccall "utimensat" c_utimensat
:: CInt -> CString -> Ptr CTimeSpec -> CInt -> IO CInt
{-# LINE 48 "libraries/directory/System/Directory/Internal/C_utimensat.hsc" #-}