module Yi.Misc
where
import Data.List
( isPrefixOf
, (\\)
, filter
)
import System.FriendlyPath
( expandTilda
, isAbsolute'
)
import System.FilePath
( takeDirectory
, (</>)
, addTrailingPathSeparator
, hasTrailingPathSeparator
, takeFileName
)
import System.Directory
( doesDirectoryExist
, getDirectoryContents
, getCurrentDirectory
, canonicalizePath
)
import Control.Monad.Trans (MonadIO (..))
import Prelude ()
import Yi.Core
import Yi.MiniBuffer
( withMinibuffer
, simpleComplete
, withMinibufferGen
)
getAppropriateFiles :: Maybe String -> String -> YiM (String, [ String ])
getAppropriateFiles start s = do
curDir <- case start of
Nothing -> do bufferPath <- withBuffer $ gets file
liftIO $ getFolder bufferPath
(Just path) -> return path
let sDir = if hasTrailingPathSeparator s then s else takeDirectory s
searchDir = if null sDir then curDir
else if isAbsolute' sDir then sDir
else curDir </> sDir
searchDir' <- liftIO $ expandTilda searchDir
let fixTrailingPathSeparator f = do
isDir <- doesDirectoryExist (searchDir' </> f)
return $ if isDir then addTrailingPathSeparator f else f
files <- liftIO $ getDirectoryContents searchDir'
let files' = files \\ [ ".", ".." ]
fs <- liftIO $ mapM fixTrailingPathSeparator files'
let matching = filter (isPrefixOf $ takeFileName s) fs
return (sDir, matching)
getFolder :: Maybe String -> IO String
getFolder Nothing = getCurrentDirectory
getFolder (Just path) = do
isDir <- doesDirectoryExist path
let dir = if isDir then path else takeDirectory path
if null dir then getCurrentDirectory else return dir
matchingFileNames :: Maybe String -> String -> YiM [String]
matchingFileNames start s = do
(sDir, files) <- getAppropriateFiles start s
return $ fmap (sDir </>) files
adjBlock :: Int -> BufferM ()
adjBlock x = withSyntaxB' (\m s -> modeAdjustBlock m s x)
adjIndent :: IndentBehaviour -> BufferM ()
adjIndent ib = withSyntaxB' (\m s -> modeIndent m s ib)
promptFile :: String -> (String -> YiM ()) -> YiM ()
promptFile prompt act = do maybePath <- withBuffer $ gets file
startPath <- addTrailingPathSeparator <$> (liftIO $ canonicalizePath =<< getFolder maybePath)
withMinibufferGen startPath (findFileHint startPath) prompt (simpleComplete $ matchingFileNames (Just startPath)) act
findFileHint :: String -> String -> YiM [String]
findFileHint startPath s = snd <$> getAppropriateFiles (Just startPath) s