| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Haskell.GhcMod.PathsAndFiles
- type DirPath = FilePath
- type FileName = String
- newtype UnString = UnString {}
- findCabalFile :: FilePath -> IO (Maybe FilePath)
- findStackConfigFile :: FilePath -> IO (Maybe FilePath)
- getSandboxDb :: Cradle -> IO (Maybe GhcPkgDb)
- extractSandboxDbDir :: String -> Maybe FilePath
- isCabalFile :: FilePath -> Bool
- takeExtension' :: FilePath -> String
- findFileInParentsP :: (FilePath -> Bool) -> FilePath -> IO [(DirPath, [FileName])]
- getFilesP :: (FilePath -> Bool) -> DirPath -> IO [FileName]
- findCabalSandboxDir :: FilePath -> IO (Maybe FilePath)
- zipMapM :: Monad m => (a -> m c) -> [a] -> m [(a, c)]
- parents :: FilePath -> [FilePath]
- setupConfigFile :: Cradle -> FilePath
- sandboxConfigFile :: Cradle -> FilePath
- sandboxConfigFileName :: String
- setupConfigPath :: FilePath -> FilePath
- macrosHeaderPath :: FilePath
- ghcSandboxPkgDbDir :: String -> String
- packageCache :: String
- symbolCache :: Cradle -> FilePath
- symbolCacheFile :: String
- resolvedComponentsCacheFile :: FilePath -> FilePath
- cabalHelperCacheFile :: FilePath -> FilePath
- mergedPkgOptsCacheFile :: FilePath -> FilePath
- pkgDbStackCacheFile :: FilePath -> FilePath
- findCustomPackageDbFile :: FilePath -> IO (Maybe FilePath)
- module Language.Haskell.GhcMod.Caching
Documentation
findCabalFile :: FilePath -> IO (Maybe FilePath) Source
findCabalFiles dir. Searches for a .cabal files in dir's parent
directories. The first parent directory containing more than one cabal file
is assumed to be the project directory. If only one cabal file exists in this
directory it is returned otherwise findCabalFiles throws GMENoCabalFile
or GMETooManyCabalFiles
extractSandboxDbDir :: String -> Maybe FilePath Source
Extract the sandbox package db directory from the cabal.sandbox.config file. Exception is thrown if the sandbox config file is broken.
isCabalFile :: FilePath -> Bool Source
>>>isCabalFile "/home/user/.cabal"False
takeExtension' :: FilePath -> String Source
>>>takeExtension' "/some/dir/bla.cabal"".cabal"
>>>takeExtension' "some/reldir/bla.cabal"".cabal"
>>>takeExtension' "bla.cabal"".cabal"
>>>takeExtension' ".cabal"""
findFileInParentsP :: (FilePath -> Bool) -> FilePath -> IO [(DirPath, [FileName])] Source
findFileInParentsP p dir Look for files satisfying p in dir and all
it's parent directories.
getFilesP :: (FilePath -> Bool) -> DirPath -> IO [FileName] Source
getFilesP p dir. Find all files satisfying p in .cabal in dir.
parents :: FilePath -> [FilePath] Source
parents dir. Returns all parent directories of dir including dir.
Examples
>>>parents "foo"["foo"]
>>>parents "/foo"["/foo","/"]
>>>parents "/foo/bar"["/foo/bar","/foo","/"]
>>>parents "foo/bar"["foo/bar","foo"]
setupConfigFile :: Cradle -> FilePath Source
setupConfigPath :: FilePath -> FilePath Source
Path to LocalBuildInfo file, usually dist/setup-config
ghcSandboxPkgDbDir :: String -> String Source
symbolCache :: Cradle -> FilePath Source
Filename of the symbol table cache file.