Skip to content
Snippets Groups Projects
Commit dd3ba275 authored by Ian Lynagh's avatar Ian Lynagh
Browse files

Switch to using the time package, rather than old-time

parent 2fc797b0
No related branches found
No related tags found
No related merge requests found
...@@ -14,15 +14,13 @@ module Trace.Hpc.Mix ...@@ -14,15 +14,13 @@ module Trace.Hpc.Mix
, CondBox(..) , CondBox(..)
, mixCreate , mixCreate
, readMix , readMix
, Trace.Hpc.Mix.getModificationTime
, createMixEntryDom , createMixEntryDom
, MixEntryDom , MixEntryDom
) )
where where
import System.Time (ClockTime(..))
import System.Directory (getModificationTime)
import Data.Maybe (catMaybes) import Data.Maybe (catMaybes)
import Data.Time
import Data.Tree import Data.Tree
import Data.Char import Data.Char
...@@ -41,16 +39,12 @@ import Trace.Hpc.Tix ...@@ -41,16 +39,12 @@ import Trace.Hpc.Tix
data Mix = Mix data Mix = Mix
FilePath -- location of original file FilePath -- location of original file
Integer -- time (in seconds) of original file's last update, since 1970. UTCTime -- time of original file's last update
Hash -- hash of mix entry + timestamp Hash -- hash of mix entry + timestamp
Int -- tab stop value. Int -- tab stop value.
[MixEntry] -- entries [MixEntry] -- entries
deriving (Show,Read) deriving (Show,Read)
-- We would rather use ClockTime in Mix, but ClockTime has no Read instance in 6.4 and before,
-- but does in 6.6. Definining the instance for ClockTime here is the Wrong Thing to do,
-- because if some other program also defined that instance, we will not be able to compile.
type MixEntry = (HpcPos, BoxLabel) type MixEntry = (HpcPos, BoxLabel)
data BoxLabel = ExpBox Bool -- isAlt data BoxLabel = ExpBox Bool -- isAlt
...@@ -111,13 +105,6 @@ readMix dirNames mod' = do ...@@ -111,13 +105,6 @@ readMix dirNames mod' = do
mixName :: FilePath -> String -> String mixName :: FilePath -> String -> String
mixName dirName name = dirName ++ "/" ++ name ++ ".mix" mixName dirName name = dirName ++ "/" ++ name ++ ".mix"
-- | Get modification time of a file.
getModificationTime :: FilePath -> IO Integer
getModificationTime file = do
(TOD sec _) <- System.Directory.getModificationTime file
return $ sec
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
type MixEntryDom a = Tree (HpcPos,a) type MixEntryDom a = Tree (HpcPos,a)
......
...@@ -27,7 +27,7 @@ Library ...@@ -27,7 +27,7 @@ Library
if flag(small_base) if flag(small_base)
Build-Depends: base >= 3 && < 5, Build-Depends: base >= 3 && < 5,
directory >= 1 && < 1.2, directory >= 1 && < 1.2,
old-time >= 1 && < 1.1, time < 1.5,
containers >= 0.1 && < 0.5 containers >= 0.1 && < 0.5
else else
Build-Depends: base < 3 Build-Depends: base < 3
......
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