module StaticLS.FilePath (modToFilePath, subRootExtensionFilepath) where
import Control.Monad.IO.Class
import Control.Monad.Trans.Maybe
import qualified Data.List as List
import qualified Data.List.Extra as List
import qualified GHC.Plugins as GHC
import StaticLS.SrcFiles
import qualified System.Directory as Dir
import System.FilePath ((-<.>), (</>))
modToFilePath :: GHC.ModuleName -> String -> FilePath
modToFilePath :: ModuleName -> String -> String
modToFilePath ModuleName
modName String
ext =
ModuleName -> String
GHC.moduleNameSlashes ModuleName
modName String -> String -> String
-<.> String
ext
subRootExtensionFilepath :: (MonadIO m) => FilePath -> FilePath -> String -> FilePath -> MaybeT m FilePath
subRootExtensionFilepath :: forall (m :: * -> *).
MonadIO m =>
String -> String -> String -> String -> MaybeT m String
subRootExtensionFilepath String
wsRoot String
parent String
extension String
srcPath =
do
String
absoluteRoot <- IO String -> MaybeT m String
forall a. IO a -> MaybeT m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> MaybeT m String) -> IO String -> MaybeT m String
forall a b. (a -> b) -> a -> b
$ String -> IO String
Dir.makeAbsolute String
wsRoot
let absoluteSrcDirs :: [String]
absoluteSrcDirs = (String
absoluteRoot String -> String -> String
</>) (String -> String) -> [String] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [String]
srcDirs
String
absoluteSrcPath <- IO String -> MaybeT m String
forall a. IO a -> MaybeT m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> MaybeT m String) -> IO String -> MaybeT m String
forall a b. (a -> b) -> a -> b
$ String -> IO String
Dir.makeAbsolute String
srcPath
let noPrefixSrcPath :: String
noPrefixSrcPath =
(String -> String -> String) -> String -> [String] -> String
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' ((String -> String -> String) -> String -> String -> String
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> String -> String
forall a. Eq a => [a] -> [a] -> [a]
List.dropPrefix) String
absoluteSrcPath [String]
absoluteSrcDirs
newPath :: String
newPath = String
absoluteRoot String -> String -> String
</> String
parent String -> String -> String
</> String
noPrefixSrcPath String -> String -> String
-<.> String
extension
Bool
True <- IO Bool -> MaybeT m Bool
forall a. IO a -> MaybeT m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> MaybeT m Bool) -> IO Bool -> MaybeT m Bool
forall a b. (a -> b) -> a -> b
$ String -> IO Bool
Dir.doesFileExist String
newPath
String -> MaybeT m String
forall a. a -> MaybeT m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
newPath