Skip to content
Snippets Groups Projects
Commit 3e451809 authored by Thomas Miedema's avatar Thomas Miedema
Browse files

Use System.FilePath functions instead of (++)

parent cf887060
No related branches found
No related tags found
No related merge requests found
...@@ -27,6 +27,8 @@ import Data.Time (UTCTime) ...@@ -27,6 +27,8 @@ import Data.Time (UTCTime)
import Data.Tree import Data.Tree
import Data.Char import Data.Char
import System.FilePath
-- a module index records the attributes of each tick-box that has -- a module index records the attributes of each tick-box that has
-- been introduced in that module, accessed by tick-number position -- been introduced in that module, accessed by tick-number position
-- in the list -- in the list
...@@ -107,7 +109,7 @@ readMix dirNames mod' = do ...@@ -107,7 +109,7 @@ readMix dirNames mod' = do
_ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames _ -> error $ "can not find " ++ modName ++ " in " ++ show dirNames
mixName :: FilePath -> String -> String mixName :: FilePath -> String -> String
mixName dirName name = dirName ++ "/" ++ name ++ ".mix" mixName dirName name = dirName </> name <.> "mix"
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
......
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
#ifdef __GLASGOW_HASKELL__ #if __GLASGOW_HASKELL__ >= 704
{-# LANGUAGE Safe #-} {-# 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 #endif
------------------------------------------------------------ ------------------------------------------------------------
-- Andy Gill and Colin Runciman, June 2006 -- Andy Gill and Colin Runciman, June 2006
...@@ -12,7 +16,8 @@ module Trace.Hpc.Tix(Tix(..), TixModule(..), ...@@ -12,7 +16,8 @@ module Trace.Hpc.Tix(Tix(..), TixModule(..),
tixModuleName, tixModuleHash, tixModuleTixs, tixModuleName, tixModuleHash, tixModuleTixs,
readTix, writeTix, getTixFileName) where readTix, writeTix, getTixFileName) where
import Data.List (isSuffixOf) import System.FilePath (replaceExtension)
import Trace.Hpc.Util (Hash, catchIO) import Trace.Hpc.Util (Hash, catchIO)
-- | 'Tix' is the storage format for our dynamic information about -- | 'Tix' is the storage format for our dynamic information about
...@@ -52,15 +57,7 @@ writeTix :: String ...@@ -52,15 +57,7 @@ writeTix :: String
writeTix name tix = writeTix name tix =
writeFile name (show tix) writeFile name (show tix)
{-
tixName :: String -> String
tixName name = name ++ ".tix"
-}
-- | 'getTixFullName' takes a binary or @.tix@-file name, -- | 'getTixFullName' takes a binary or @.tix@-file name,
-- and normalizes it into a @.tix@-file name. -- and normalizes it into a @.tix@-file name.
getTixFileName :: String -> String getTixFileName :: String -> String
getTixFileName str | ".tix" `isSuffixOf` str getTixFileName str = replaceExtension str "tix"
= str
| otherwise
= str ++ ".tix"
...@@ -38,5 +38,6 @@ Library ...@@ -38,5 +38,6 @@ Library
base >= 4.4.1 && < 4.9, base >= 4.4.1 && < 4.9,
containers >= 0.4.1 && < 0.6, containers >= 0.4.1 && < 0.6,
directory >= 1.1 && < 1.3, directory >= 1.1 && < 1.3,
filepath >= 1 && < 1.5,
time >= 1.2 && < 1.6 time >= 1.2 && < 1.6
ghc-options: -Wall ghc-options: -Wall
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