{-# INCLUDE <bindings.macros.h> #-}
{-# INCLUDE <time.h> #-}
{-# LINE 1 "src/Bindings/Posix/Time.hsc" #-}

{-# LINE 2 "src/Bindings/Posix/Time.hsc" #-}

{-# LINE 3 "src/Bindings/Posix/Time.hsc" #-}

-- | <http://www.opengroup.org/onlinepubs/9699919799/basedefs/time.h.html>

module Bindings.Posix.Time where
import Foreign
import Foreign.C

data C'timespec = C'timespec{
{-# LINE 11 "src/Bindings/Posix/Time.hsc" #-}

  timespec'tv_sec :: CTime
{-# LINE 12 "src/Bindings/Posix/Time.hsc" #-}
,
  timespec'tv_nsec :: CLong
{-# LINE 13 "src/Bindings/Posix/Time.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'timespec where
  sizeOf _ = 8
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    return $ C'timespec v0 v1
  poke p (C'timespec v0 v1) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    return ()

{-# LINE 14 "src/Bindings/Posix/Time.hsc" #-}

foreign import ccall "&tzname" p'tzname
  :: Ptr (Ptr CString)

{-# LINE 16 "src/Bindings/Posix/Time.hsc" #-}