|
| 1 | +{- Utility functions for manipulating filepaths and directories. |
| 2 | +-} |
1 | 3 | module DirectoryUtils where |
2 | 4 |
|
3 | | -import Control.Exception (Exception, catch) |
4 | | -import Data.List (dropWhileEnd, isInfixOf, isSuffixOf) |
5 | | -import Data.List.Extra (takeWhileEnd) |
6 | | -import qualified Data.Sequence as S |
| 5 | +import Control.Concurrent |
| 6 | +import Control.Exception (catch) |
| 7 | +import Data.Char |
| 8 | +import Data.List (isSuffixOf) |
| 9 | +import Data.List.Extra (upper) |
| 10 | +import qualified Data.Map as M |
| 11 | +import qualified Data.Sequence as S |
7 | 12 | import System.Directory |
8 | | -import System.FilePath (takeDirectory, takeFileName, (</>)) |
9 | | -import System.Info (os) |
| 13 | +import System.FilePath (takeBaseName, takeFileName, (</>)) |
| 14 | +import System.Info (os) |
| 15 | + |
| 16 | +import Types |
10 | 17 |
|
11 | 18 | isWindows :: Bool |
12 | 19 | isWindows = os `notElem` ["linux", "unix", "darwin"] |
13 | 20 |
|
| 21 | +isHaskellFile :: FilePath -> Bool |
| 22 | +isHaskellFile = isSuffixOf ".hs" |
| 23 | + |
| 24 | +-- Probably a good idea to first check that it is a Haskell file first |
| 25 | +haskellModuleName :: FilePath -> FilePath |
| 26 | +haskellModuleName = takeBaseName |
| 27 | + |
| 28 | +haskellFileName :: FilePath -> FilePath |
| 29 | +haskellFileName exName = exName ++ ".hs" |
| 30 | + |
| 31 | +fileContainsNotDone :: FilePath -> IO Bool |
| 32 | +fileContainsNotDone fullFp = do |
| 33 | + fileLines <- lines <$> readFile fullFp |
| 34 | + return (any isDoneLine fileLines) |
| 35 | + where |
| 36 | + isDoneLine :: String -> Bool |
| 37 | + isDoneLine l = (upper . filter (not . isSpace) $ l) == "--IAMNOTDONE" |
| 38 | + |
| 39 | +fullExerciseFp :: FilePath -> FilePath -> ExerciseInfo -> FilePath |
| 40 | +fullExerciseFp projectRoot exercisesExt (ExerciseInfo exName exDir _ _) = |
| 41 | + projectRoot </> exercisesExt </> exDir </> haskellFileName exName |
| 42 | + |
| 43 | +withFileLock :: FilePath -> ProgramConfig -> IO a -> IO a |
| 44 | +withFileLock fp config action = case M.lookup fp (fileLocks config) of |
| 45 | + Nothing -> action |
| 46 | + Just lock -> do |
| 47 | + putMVar lock () |
| 48 | + result <- action |
| 49 | + takeMVar lock |
| 50 | + return result |
| 51 | + |
| 52 | +-- Create a directory. Run the action depending on that directory, |
| 53 | +-- and then clean the directory up. |
| 54 | +withDirectory :: FilePath -> IO a -> IO a |
| 55 | +withDirectory dirPath action = do |
| 56 | + createDirectoryIfMissing True dirPath |
| 57 | + res <- action |
| 58 | + removeDirectoryRecursive dirPath |
| 59 | + return res |
| 60 | + |
14 | 61 | returnIfDirExists :: FilePath -> IO (Maybe FilePath) |
15 | 62 | returnIfDirExists fp = do |
16 | 63 | exists <- doesDirectoryExist fp |
17 | 64 | if exists |
18 | 65 | then return (Just fp) |
19 | 66 | else return Nothing |
20 | 67 |
|
| 68 | +---------- Directory Search Functions ---------- |
| 69 | + |
21 | 70 | searchForDirectoryContaining :: FilePath -> String -> IO (Maybe FilePath) |
22 | 71 | searchForDirectoryContaining searchRoot directoryToFind = fpBFS predicate (S.singleton searchRoot) |
23 | 72 | where |
|
0 commit comments