[commit: packages/hpc] wip/T9619: Use System.FilePath functions instead of (++) (3e45180)

git at git.haskell.org git at git.haskell.org
Wed Mar 11 16:35:07 UTC 2015


Repository : ssh://git@git.haskell.org/hpc

On branch  : wip/T9619
Link       : http://git.haskell.org/packages/hpc.git/commitdiff/3e451809444c163c3caecccb3854d8745932ca93

>---------------------------------------------------------------

commit 3e451809444c163c3caecccb3854d8745932ca93
Author: Thomas Miedema <thomasmiedema at gmail.com>
Date:   Thu Mar 5 21:36:07 2015 +0100

    Use System.FilePath functions instead of (++)


>---------------------------------------------------------------

3e451809444c163c3caecccb3854d8745932ca93
 Trace/Hpc/Mix.hs |  4 +++-
 Trace/Hpc/Tix.hs | 19 ++++++++-----------
 hpc.cabal        |  1 +
 3 files changed, 12 insertions(+), 12 deletions(-)

diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs
index 28050ad..4a7fc74 100644
--- a/Trace/Hpc/Mix.hs
+++ b/Trace/Hpc/Mix.hs
@@ -27,6 +27,8 @@ import Data.Time (UTCTime)
 import Data.Tree
 import Data.Char
 
+import System.FilePath
+
 -- a module index records the attributes of each tick-box that has
 -- been introduced in that module, accessed by tick-number position
 -- in the list
@@ -107,7 +109,7 @@ readMix dirNames mod' = do
      _        -> error $ "can not find " ++ modName ++ " in " ++ show dirNames
 
 mixName :: FilePath -> String -> String
-mixName dirName name = dirName ++ "/" ++ name ++ ".mix"
+mixName dirName name = dirName </> name <.> "mix"
 
 ------------------------------------------------------------------------------
 
diff --git a/Trace/Hpc/Tix.hs b/Trace/Hpc/Tix.hs
index 2b03e0a..fa95dbf 100644
--- a/Trace/Hpc/Tix.hs
+++ b/Trace/Hpc/Tix.hs
@@ -1,6 +1,10 @@
 {-# LANGUAGE CPP #-}
-#ifdef __GLASGOW_HASKELL__
+#if __GLASGOW_HASKELL__ >= 704
 {-# LANGUAGE Safe #-}
+#elif __GLASGOW_HASKELL__ >= 702
+-- System.FilePath in filepath version 1.2.0.1 isn't marked or implied Safe,
+-- as shipped with GHC 7.2.
+{-# LANGUAGE Trustworthy #-}
 #endif
 ------------------------------------------------------------
 -- Andy Gill and Colin Runciman, June 2006
@@ -12,7 +16,8 @@ module Trace.Hpc.Tix(Tix(..), TixModule(..),
                      tixModuleName, tixModuleHash, tixModuleTixs,
                      readTix, writeTix, getTixFileName) where
 
-import Data.List (isSuffixOf)
+import System.FilePath (replaceExtension)
+
 import Trace.Hpc.Util (Hash, catchIO)
 
 -- | 'Tix' is the storage format for our dynamic information about
@@ -52,15 +57,7 @@ writeTix :: String
 writeTix name tix =
   writeFile name (show tix)
 
-{-
-tixName :: String -> String
-tixName name = name ++ ".tix"
--}
-
 -- | 'getTixFullName' takes a binary or @.tix at -file name,
 -- and normalizes it into a @.tix at -file name.
 getTixFileName :: String -> String
-getTixFileName str | ".tix" `isSuffixOf` str
-                   = str
-                   | otherwise
-                   = str ++ ".tix"
+getTixFileName str = replaceExtension str "tix"
diff --git a/hpc.cabal b/hpc.cabal
index 857faba..4e5b6f0 100644
--- a/hpc.cabal
+++ b/hpc.cabal
@@ -38,5 +38,6 @@ Library
         base       >= 4.4.1 && < 4.9,
         containers >= 0.4.1 && < 0.6,
         directory  >= 1.1   && < 1.3,
+        filepath   >= 1     && < 1.5,
         time       >= 1.2   && < 1.6
     ghc-options: -Wall



More information about the ghc-commits mailing list