module SFML.System.Time
(
    Time
,   timeZero
,   asSeconds
,   asMilliseconds
,   asMicroseconds
,   seconds
,   milliseconds
,   microseconds
)
where
import Control.Monad ((>=>))
import Data.Int (Int64, Int32)
import Foreign.C.Types
import Foreign.Marshal.Alloc (alloca)
import Foreign.Ptr
import Foreign.Storable
import System.IO.Unsafe (unsafePerformIO)
sizeInt64 = (8)
type Time = Int64
timeZero :: Time
timeZero = 0
asSeconds :: Time -> Float
asSeconds = realToFrac . sfTime_asSeconds
foreign import ccall unsafe "sfTime_asSeconds"
    sfTime_asSeconds :: Time -> CFloat
asMilliseconds :: Time -> Int
asMilliseconds t = fromIntegral $ sfTime_asMilliseconds t
foreign import ccall unsafe "sfTime_asMilliseconds"
    sfTime_asMilliseconds :: Time -> Int32
asMicroseconds :: Time -> Int64
asMicroseconds t = sfTime_asMicroseconds t
foreign import ccall unsafe "sfTime_asMicroseconds"
    sfTime_asMicroseconds :: Time -> Int64
seconds
    :: Float 
    -> Time
seconds s = unsafePerformIO $ alloca $ \ptr -> sfSeconds_helper (realToFrac s) ptr >> peek ptr
foreign import ccall unsafe "sfSeconds_helper"
    sfSeconds_helper :: CFloat -> Ptr Time -> IO ()
milliseconds
    :: Int 
    -> Time
milliseconds t =
    unsafePerformIO $ alloca $ \ptr -> sfMilliseconds_helper (fromIntegral t) ptr >> peek ptr
foreign import ccall unsafe "sfMilliseconds_helper"
    sfMilliseconds_helper :: Int32 -> Ptr Time -> IO ()
microseconds
    :: Int64 
    -> Time
microseconds t = unsafePerformIO $ alloca $ \ptr -> sfMicroseconds_helper t ptr >> peek ptr
foreign import ccall unsafe "sfMicroseconds_helper"
    sfMicroseconds_helper :: Int64 -> Ptr Time -> IO ()