Skip to content

Commit

Permalink
Remove ‘Path.IO’, switch to ‘path-io’ package
Browse files Browse the repository at this point in the history
  • Loading branch information
mrkkrp committed Jan 31, 2016
1 parent b2a182d commit 46a7c46
Show file tree
Hide file tree
Showing 37 changed files with 307 additions and 618 deletions.
4 changes: 2 additions & 2 deletions src/Data/Binary/VersionTagged.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ import Data.Monoid ((<>))
import Data.Typeable (Typeable)
import Control.Exception.Enclosed (tryAnyDeep)
import Path
import Path.IO (createTree)
import Path.IO (ensureDir)
import qualified Data.Text as T

type BinarySchema a = (Binary a, NFData a, HasStructuralInfo a, HasSemanticVersion a)
Expand All @@ -40,7 +40,7 @@ taggedEncodeFile :: (BinarySchema a, MonadIO m)
-> a
-> m ()
taggedEncodeFile fp x = liftIO $ do
createTree (parent fp)
ensureDir (parent fp)
BinaryTagged.taggedEncodeFile (toFilePath fp) x

-- | Read from the given file. If the read fails, run the given action and
Expand Down
6 changes: 3 additions & 3 deletions src/Path/Find.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ import Control.Monad.IO.Class
import System.IO.Error (isPermissionError)
import Data.List
import Path
import Path.IO
import Path.IO hiding (findFiles)

-- | Find the location of a file matching the given predicate.
findFileUp :: (MonadIO m,MonadThrow m)
Expand All @@ -41,7 +41,7 @@ findPathUp :: (MonadIO m,MonadThrow m)
-> Maybe (Path Abs Dir) -- ^ Do not ascend above this directory.
-> m (Maybe (Path Abs t)) -- ^ Absolute path.
findPathUp pathType dir p upperBound =
do entries <- listDirectory dir
do entries <- listDir dir
case find p (pathType entries) of
Just path -> return (Just path)
Nothing | Just dir == upperBound -> return Nothing
Expand All @@ -57,7 +57,7 @@ findFiles dir p traversep =
do (dirs,files) <- catchJust (\ e -> if isPermissionError e
then Just ()
else Nothing)
(listDirectory dir)
(listDir dir)
(\ _ -> return ([], []))
subResults <-
forM dirs
Expand Down
265 changes: 0 additions & 265 deletions src/Path/IO.hs

This file was deleted.

18 changes: 9 additions & 9 deletions src/Stack/Build/Cache.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ module Stack.Build.Cache
) where

import Control.Exception.Enclosed (handleIO)
import Control.Monad.Catch (MonadThrow)
import Control.Monad.Catch (MonadThrow, MonadCatch)
import Control.Monad.IO.Class
import Control.Monad.Logger (MonadLogger)
import Control.Monad.Reader
Expand Down Expand Up @@ -59,15 +59,15 @@ getInstalledExes :: (MonadReader env m, HasEnvConfig env, MonadIO m, MonadThrow
=> InstallLocation -> m [PackageIdentifier]
getInstalledExes loc = do
dir <- exeInstalledDir loc
(_, files) <- liftIO $ handleIO (const $ return ([], [])) $ listDirectory dir
(_, files) <- liftIO $ handleIO (const $ return ([], [])) $ listDir dir
return $ mapMaybe (parsePackageIdentifierFromString . toFilePath . filename) files

-- | Mark the given executable as installed
markExeInstalled :: (MonadReader env m, HasEnvConfig env, MonadIO m, MonadThrow m)
=> InstallLocation -> PackageIdentifier -> m ()
markExeInstalled loc ident = do
dir <- exeInstalledDir loc
createTree dir
ensureDir dir
ident' <- parseRelFile $ packageIdentifierString ident
let fp = toFilePath $ dir </> ident'
-- TODO consideration for the future: list all of the executables
Expand All @@ -76,12 +76,12 @@ markExeInstalled loc ident = do
liftIO $ writeFile fp "Installed"

-- | Mark the given executable as not installed
markExeNotInstalled :: (MonadReader env m, HasEnvConfig env, MonadIO m, MonadThrow m)
markExeNotInstalled :: (MonadReader env m, HasEnvConfig env, MonadIO m, MonadCatch m)
=> InstallLocation -> PackageIdentifier -> m ()
markExeNotInstalled loc ident = do
dir <- exeInstalledDir loc
ident' <- parseRelFile $ packageIdentifierString ident
removeFileIfExists (dir </> ident')
ignoringAbsence (removeFile $ dir </> ident')

-- | Stored on disk to know whether the flags have changed or any
-- files have changed.
Expand Down Expand Up @@ -145,15 +145,15 @@ writeCabalMod :: (MonadIO m, MonadReader env m, HasConfig env, MonadThrow m, Mon
writeCabalMod dir = writeCache dir configCabalMod

-- | Delete the caches for the project.
deleteCaches :: (MonadIO m, MonadReader env m, HasConfig env, MonadLogger m, MonadThrow m, HasEnvConfig env)
deleteCaches :: (MonadIO m, MonadReader env m, HasConfig env, MonadLogger m, MonadCatch m, HasEnvConfig env)
=> Path Abs Dir -> m ()
deleteCaches dir = do
{- FIXME confirm that this is acceptable to remove
bfp <- buildCacheFile dir
removeFileIfExists bfp
-}
cfp <- configCacheFile dir
removeFileIfExists cfp
ignoringAbsence (removeFile cfp)

-- | Write to a cache.
writeCache :: (BinarySchema a, MonadIO m)
Expand Down Expand Up @@ -191,7 +191,7 @@ writeFlagCache :: (MonadIO m, MonadReader env m, HasEnvConfig env, MonadThrow m)
writeFlagCache gid cache = do
file <- flagCacheFile gid
liftIO $ do
createTree (parent file)
ensureDir (parent file)
taggedEncodeFile file cache

-- | Mark a test suite as having succeeded
Expand Down Expand Up @@ -289,7 +289,7 @@ writePrecompiledCache :: (MonadThrow m, MonadReader env m, HasEnvConfig env, Mon
-> m ()
writePrecompiledCache baseConfigOpts pkgident copts depIDs mghcPkgId exes = do
file <- precompiledCacheFile pkgident copts depIDs
createTree $ parent file
ensureDir (parent file)
mlibpath <-
case mghcPkgId of
Executable _ -> return Nothing
Expand Down
Loading

0 comments on commit 46a7c46

Please sign in to comment.