Skip to content
Snippets Groups Projects
Commit d9b0c354 authored by Cheng Shao's avatar Cheng Shao
Browse files

Finish remaining fixes for the JS backend

The JS backend doesn't support capi calling convention for the time
being. This patch delivers the remaining fixes, and is indeed tested
to work via a ghc validate pipeline.
parent ada2277a
No related merge requests found
...@@ -30,11 +30,22 @@ instance Storable CTimespec where ...@@ -30,11 +30,22 @@ instance Storable CTimespec where
#{poke struct timespec, tv_sec } p s #{poke struct timespec, tv_sec } p s
#{poke struct timespec, tv_nsec} p ns #{poke struct timespec, tv_nsec} p ns
#if defined(javascript_HOST_ARCH)
foreign import ccall unsafe "time.h clock_gettime"
clock_gettime :: ClockID -> Ptr CTimespec -> IO CInt
foreign import ccall unsafe "time.h clock_getres"
clock_getres :: ClockID -> Ptr CTimespec -> IO CInt
#else
foreign import capi unsafe "time.h clock_gettime" foreign import capi unsafe "time.h clock_gettime"
clock_gettime :: ClockID -> Ptr CTimespec -> IO CInt clock_gettime :: ClockID -> Ptr CTimespec -> IO CInt
foreign import capi unsafe "time.h clock_getres" foreign import capi unsafe "time.h clock_getres"
clock_getres :: ClockID -> Ptr CTimespec -> IO CInt clock_getres :: ClockID -> Ptr CTimespec -> IO CInt
#endif
-- | Get the resolution of the given clock. -- | Get the resolution of the given clock.
clockGetRes :: ClockID -> IO (Either Errno CTimespec) clockGetRes :: ClockID -> IO (Either Errno CTimespec)
clockGetRes clockid = alloca $ \ptspec -> do clockGetRes clockid = alloca $ \ptspec -> do
......
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-} {-# LANGUAGE Safe #-}
#if !defined(javascript_HOST_ARCH)
{-# LANGUAGE CApiFFI #-}
#endif
module Data.Time.Clock.Internal.CTimeval where module Data.Time.Clock.Internal.CTimeval where
...@@ -24,8 +26,16 @@ instance Storable CTimeval where ...@@ -24,8 +26,16 @@ instance Storable CTimeval where
pokeElemOff (castPtr p) 0 s pokeElemOff (castPtr p) 0 s
pokeElemOff (castPtr p) 1 mus pokeElemOff (castPtr p) 1 mus
#if defined(javascript_HOST_ARCH)
foreign import ccall unsafe "sys/time.h gettimeofday" gettimeofday :: Ptr CTimeval -> Ptr () -> IO CInt
#else
foreign import capi unsafe "sys/time.h gettimeofday" gettimeofday :: Ptr CTimeval -> Ptr () -> IO CInt foreign import capi unsafe "sys/time.h gettimeofday" gettimeofday :: Ptr CTimeval -> Ptr () -> IO CInt
#endif
-- | Get the current POSIX time from the system clock. -- | Get the current POSIX time from the system clock.
getCTimeval :: IO CTimeval getCTimeval :: IO CTimeval
getCTimeval = getCTimeval =
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment