{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ViewPatterns #-}
module Ormolu.Utils.IO
( findClosestFileSatisfying,
withIORefCache,
)
where
import Control.Exception (catch, throwIO)
import Control.Monad.IO.Class
import Data.IORef
import Data.Map.Lazy (Map)
import Data.Map.Lazy qualified as M
import System.Directory
import System.FilePath
import System.IO.Error (isDoesNotExistError)
findClosestFileSatisfying ::
(MonadIO m) =>
(FilePath -> Bool) ->
FilePath ->
m (Maybe FilePath)
findClosestFileSatisfying :: forall (m :: * -> *).
MonadIO m =>
(FilePath -> Bool) -> FilePath -> m (Maybe FilePath)
findClosestFileSatisfying FilePath -> Bool
isRightFile FilePath
rootOfSearch = IO (Maybe FilePath) -> m (Maybe FilePath)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FilePath) -> m (Maybe FilePath))
-> IO (Maybe FilePath) -> m (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ do
FilePath
parentDir <- FilePath -> FilePath
takeDirectory (FilePath -> FilePath) -> IO FilePath -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO FilePath
makeAbsolute FilePath
rootOfSearch
[FilePath]
dirEntries <-
FilePath -> IO [FilePath]
listDirectory FilePath
parentDir IO [FilePath] -> (IOError -> IO [FilePath]) -> IO [FilePath]
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` \case
(IOError -> Bool
isDoesNotExistError -> Bool
True) -> [FilePath] -> IO [FilePath]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
IOError
e -> IOError -> IO [FilePath]
forall e a. Exception e => e -> IO a
throwIO IOError
e
let searchAtParentDirLevel :: [FilePath] -> IO (Maybe FilePath)
searchAtParentDirLevel = \case
[] -> Maybe FilePath -> IO (Maybe FilePath)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe FilePath
forall a. Maybe a
Nothing
FilePath
x : [FilePath]
xs ->
if FilePath -> Bool
isRightFile FilePath
x
then
FilePath -> IO Bool
doesFileExist (FilePath
parentDir FilePath -> FilePath -> FilePath
</> FilePath
x) IO Bool -> (Bool -> IO (Maybe FilePath)) -> IO (Maybe FilePath)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
True -> Maybe FilePath -> IO (Maybe FilePath)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
x)
Bool
False -> [FilePath] -> IO (Maybe FilePath)
searchAtParentDirLevel [FilePath]
xs
else [FilePath] -> IO (Maybe FilePath)
searchAtParentDirLevel [FilePath]
xs
[FilePath] -> IO (Maybe FilePath)
searchAtParentDirLevel [FilePath]
dirEntries IO (Maybe FilePath)
-> (Maybe FilePath -> IO (Maybe FilePath)) -> IO (Maybe FilePath)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just FilePath
foundFile -> Maybe FilePath -> IO (Maybe FilePath)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe FilePath -> IO (Maybe FilePath))
-> (FilePath -> Maybe FilePath) -> FilePath -> IO (Maybe FilePath)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath -> IO (Maybe FilePath))
-> FilePath -> IO (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ FilePath
parentDir FilePath -> FilePath -> FilePath
</> FilePath
foundFile
Maybe FilePath
Nothing ->
if FilePath -> Bool
isDrive FilePath
parentDir
then Maybe FilePath -> IO (Maybe FilePath)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe FilePath
forall a. Maybe a
Nothing
else (FilePath -> Bool) -> FilePath -> IO (Maybe FilePath)
forall (m :: * -> *).
MonadIO m =>
(FilePath -> Bool) -> FilePath -> m (Maybe FilePath)
findClosestFileSatisfying FilePath -> Bool
isRightFile FilePath
parentDir
withIORefCache :: (Ord k) => IORef (Map k v) -> k -> IO v -> IO v
withIORefCache :: forall k v. Ord k => IORef (Map k v) -> k -> IO v -> IO v
withIORefCache IORef (Map k v)
cacheRef k
k IO v
action = do
Map k v
cache <- IORef (Map k v) -> IO (Map k v)
forall a. IORef a -> IO a
readIORef IORef (Map k v)
cacheRef
case k -> Map k v -> Maybe v
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup k
k Map k v
cache of
Just v
v -> v -> IO v
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure v
v
Maybe v
Nothing -> do
v
v <- IO v
action
IORef (Map k v) -> (Map k v -> Map k v) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' IORef (Map k v)
cacheRef (k -> v -> Map k v -> Map k v
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert k
k v
v)
v -> IO v
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure v
v