[Haskell-cafe] Is there a better way to convert from UTCTime to EpochTime ?

David Virebayre dav.vire+haskell at gmail.com
Wed Nov 10 07:09:08 EST 2010


I want to set a file's modification time to the time I got from exif data.

To get the time from exif, I found :
Graphics.Exif.getTag :: Exif -> String -> IO (Maybe String)

To set the file modification time, I found :
System.Posix.Files.setFileTimes :: FilePath -> EpochTime -> EpochTime -> IO ()

Assuming I do find a Time in Exif, I need to convert a String to an EpochTime.

- With parseTime I can get a UTCTime.
- With utcTimeToPOSIXSeconds I can get a POSIXTime
- With a POSIXTime I can more or less get an EpochTime

To convert from a UTCTime to EpochTime this typechecks, but I'm not
sure it's correct :
fromIntegral . fromEnum . utcTimeToPOSIXSeconds $ etime

This is part of a function getTime that will return the time from Exif
data, if present, otherwise the file's modification time :

getTime (path,stat) = do
  let ftime                 = modificationTime $ stat
      err (SomeException _) = return ftime
  time <- liftIO $ handle err $ do
    exif <- Exif.fromFile path
    let getExifTime = MaybeT . liftIO . Exif.getTag exif
    res <- runMaybeT $ do
      tmp <- msum . map getExifTime $ [ "DateTimeOriginal",
"DateTimeDigitized", "DateTime" ]
      MaybeT . return . parseTime defaultTimeLocale "%Y:%m:%d %H:%M:%S" $ tmp
    case res of
      Nothing    -> return ftime
      Just etime -> return . fromIntegral . fromEnum .
utcTimeToPOSIXSeconds $ etime
  return (path,time)

Questions :

1) is there a better way to convert the time ?
2) any general comments on getTime ?

Thanks,

David.


More information about the Haskell-Cafe mailing list