Skip to content
Snippets Groups Projects
Commit f45552f6 authored by Mikhail Glushenkov's avatar Mikhail Glushenkov Committed by tibbe
Browse files

getModTime: Convert Windows time to POSIX seconds.

Fixes #1538.

(cherry picked from commit 6ce9ca28)
parent bc482215
No related merge requests found
...@@ -16,19 +16,24 @@ import System.Time (ClockTime(..), getClockTime ...@@ -16,19 +16,24 @@ import System.Time (ClockTime(..), getClockTime
#if defined mingw32_HOST_OS #if defined mingw32_HOST_OS
import Data.Int (Int32) import Data.Bits ((.|.), bitSize, unsafeShiftL)
import Data.Word (Word32) import Data.Int (Int32)
import Foreign (Ptr, allocaBytes, peekByteOff) import Data.Word (Word64)
import Foreign.C.Types (CChar) import Foreign (allocaBytes, peekByteOff)
import Foreign.C.String (withCString) import System.IO.Error (mkIOError, doesNotExistErrorType)
import System.IO.Error (mkIOError, doesNotExistErrorType) import System.Win32.Types (BOOL, DWORD, LPCTSTR, LPVOID, withTString)
type WIN32_FILE_ATTRIBUTE_DATA = Ptr ()
type LPCSTR = Ptr CChar
foreign import stdcall "Windows.h GetFileAttributesExA" foreign import stdcall "windows.h GetFileAttributesExW"
c_getFileAttributesEx :: LPCSTR -> Int32 c_getFileAttributesEx :: LPCTSTR -> Int32 -> LPVOID -> IO BOOL
-> WIN32_FILE_ATTRIBUTE_DATA -> IO Bool
getFileAttributesEx :: String -> LPVOID -> IO BOOL
getFileAttributesEx path lpFileInformation =
withTString path $ \c_path ->
c_getFileAttributesEx c_path getFileExInfoStandard lpFileInformation
getFileExInfoStandard :: Int32
getFileExInfoStandard = 0
size_WIN32_FILE_ATTRIBUTE_DATA :: Int size_WIN32_FILE_ATTRIBUTE_DATA :: Int
size_WIN32_FILE_ATTRIBUTE_DATA = 36 size_WIN32_FILE_ATTRIBUTE_DATA = 36
...@@ -36,6 +41,9 @@ size_WIN32_FILE_ATTRIBUTE_DATA = 36 ...@@ -36,6 +41,9 @@ size_WIN32_FILE_ATTRIBUTE_DATA = 36
index_WIN32_FILE_ATTRIBUTE_DATA_ftLastWriteTime_dwLowDateTime :: Int index_WIN32_FILE_ATTRIBUTE_DATA_ftLastWriteTime_dwLowDateTime :: Int
index_WIN32_FILE_ATTRIBUTE_DATA_ftLastWriteTime_dwLowDateTime = 20 index_WIN32_FILE_ATTRIBUTE_DATA_ftLastWriteTime_dwLowDateTime = 20
index_WIN32_FILE_ATTRIBUTE_DATA_ftLastWriteTime_dwHighDateTime :: Int
index_WIN32_FILE_ATTRIBUTE_DATA_ftLastWriteTime_dwHighDateTime = 24
#else #else
#if MIN_VERSION_base(4,5,0) #if MIN_VERSION_base(4,5,0)
...@@ -60,21 +68,32 @@ getModTime :: FilePath -> IO EpochTime ...@@ -60,21 +68,32 @@ getModTime :: FilePath -> IO EpochTime
#if defined mingw32_HOST_OS #if defined mingw32_HOST_OS
-- Directly against the Win32 API. -- Directly against the Win32 API.
getModTime path = withCString path $ \file -> getModTime path = allocaBytes size_WIN32_FILE_ATTRIBUTE_DATA $ \info -> do
allocaBytes size_WIN32_FILE_ATTRIBUTE_DATA $ \info -> do res <- getFileAttributesEx path info
res <- c_getFileAttributesEx file 0 info if not res
if not res then do
then do let err = mkIOError doesNotExistErrorType
let err = mkIOError doesNotExistErrorType "Distribution.Client.Compat.Time.getModTime"
"Distribution.Client.Compat.Time.getModTime" Nothing (Just path)
Nothing (Just path) ioError err
ioError err else do
else do dwLow <- peekByteOff info
dword <- peekByteOff info index_WIN32_FILE_ATTRIBUTE_DATA_ftLastWriteTime_dwLowDateTime
index_WIN32_FILE_ATTRIBUTE_DATA_ftLastWriteTime_dwLowDateTime dwHigh <- peekByteOff info
-- TODO: Convert Windows seconds to POSIX seconds. ATM we don't care index_WIN32_FILE_ATTRIBUTE_DATA_ftLastWriteTime_dwHighDateTime
-- since we only use the value for comparisons. return $! windowsTimeToPOSIXSeconds dwLow dwHigh
return $! fromIntegral (dword :: Word32) where
windowsTimeToPOSIXSeconds :: DWORD -> DWORD -> EpochTime
windowsTimeToPOSIXSeconds dwLow dwHigh =
let wINDOWS_TICK = 10000000
sEC_TO_UNIX_EPOCH = 11644473600
qwTime = (fromIntegral dwHigh `unsafeShiftL` bitSize dwHigh)
.|. (fromIntegral dwLow)
res = ((qwTime :: Word64) `div` wINDOWS_TICK)
- sEC_TO_UNIX_EPOCH
-- TODO: What if the result is not representable as POSIX seconds?
-- Probably fine to return garbage.
in fromIntegral res
#else #else
-- Directly against the unix library. -- Directly against the unix library.
......
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