module Data.UnixTime.Conv (
    formatUnixTime, formatUnixTimeGMT
  , parseUnixTime, parseUnixTimeGMT
  , webDateFormat, mailDateFormat
  , fromEpochTime, toEpochTime
  , fromClockTime, toClockTime
  ) where
import Control.Applicative
import Data.ByteString
import Data.ByteString.Unsafe
import Data.UnixTime.Types
import Foreign.C.String
import Foreign.C.Types
import Foreign.Marshal.Alloc
import System.IO.Unsafe (unsafePerformIO)
import System.Posix.Types (EpochTime)
import System.Time (ClockTime(..))
foreign import ccall unsafe "c_parse_unix_time"
        c_parse_unix_time :: CString -> CString -> IO CTime
foreign import ccall unsafe "c_parse_unix_time_gmt"
        c_parse_unix_time_gmt :: CString -> CString -> IO CTime
foreign import ccall unsafe "c_format_unix_time"
        c_format_unix_time :: CString -> CTime -> CString -> CInt -> IO CSize
foreign import ccall unsafe "c_format_unix_time_gmt"
        c_format_unix_time_gmt :: CString -> CTime -> CString -> CInt -> IO CSize
parseUnixTime :: Format -> ByteString -> UnixTime
parseUnixTime fmt str = unsafePerformIO $
    useAsCString fmt $ \cfmt ->
        useAsCString str $ \cstr -> do
            sec <- c_parse_unix_time cfmt cstr
            return $ UnixTime sec 0
parseUnixTimeGMT :: Format -> ByteString -> UnixTime
parseUnixTimeGMT fmt str = unsafePerformIO $
    useAsCString fmt $ \cfmt ->
        useAsCString str $ \cstr -> do
            sec <- c_parse_unix_time_gmt cfmt cstr
            return $ UnixTime sec 0
formatUnixTime :: Format -> UnixTime -> IO ByteString
formatUnixTime fmt t =
    formatUnixTimeHelper c_format_unix_time fmt t
formatUnixTimeGMT :: Format -> UnixTime -> ByteString
formatUnixTimeGMT fmt t =
    unsafePerformIO $ formatUnixTimeHelper c_format_unix_time_gmt fmt t
formatUnixTimeHelper
    :: (CString -> CTime -> CString -> CInt -> IO CSize)
    -> Format
    -> UnixTime
    -> IO ByteString
formatUnixTimeHelper formatFun fmt (UnixTime sec _) =
    useAsCString fmt $ \cfmt -> do
        let siz = 80
        ptr  <- mallocBytes siz
        len  <- fromIntegral <$> formatFun cfmt sec ptr (fromIntegral siz)
        ptr' <- reallocBytes ptr (len + 1)
        unsafePackMallocCString ptr' 
webDateFormat :: Format
webDateFormat = "%a, %d %b %Y %H:%M:%S GMT"
mailDateFormat :: Format
mailDateFormat = "%a, %d %b %Y %H:%M:%S %z"
fromEpochTime :: EpochTime -> UnixTime
fromEpochTime sec = UnixTime sec 0
toEpochTime :: UnixTime -> EpochTime
toEpochTime (UnixTime sec _) = sec
fromClockTime :: ClockTime -> UnixTime
fromClockTime (TOD sec psec) = UnixTime sec' usec'
  where
    sec' = fromIntegral sec
    usec' = fromIntegral $ psec `div` 1000000
toClockTime :: UnixTime -> ClockTime
toClockTime (UnixTime sec usec) = TOD sec' psec'
  where
    sec' = truncate (toRational sec)
    psec' = fromIntegral $ usec * 1000000