Skip to content

Commit

Permalink
Make the cache thread-safe
Browse files Browse the repository at this point in the history
  • Loading branch information
michaelpj authored and mrkkrp committed Jul 11, 2024
1 parent ae88081 commit 392b2bc
Show file tree
Hide file tree
Showing 3 changed files with 24 additions and 18 deletions.
9 changes: 4 additions & 5 deletions src/Ormolu/Utils/Cabal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,6 @@ where
import Control.Exception
import Control.Monad.IO.Class
import Data.ByteString qualified as B
import Data.IORef
import Data.Map.Lazy (Map)
import Data.Map.Lazy qualified as M
import Data.Maybe (maybeToList)
Expand All @@ -29,7 +28,7 @@ import Language.Haskell.Extension
import Ormolu.Config
import Ormolu.Exception
import Ormolu.Fixity
import Ormolu.Utils.IO (findClosestFileSatisfying, withIORefCache)
import Ormolu.Utils.IO (Cache, findClosestFileSatisfying, newCache, withCache)
import System.Directory
import System.FilePath
import System.IO.Unsafe (unsafePerformIO)
Expand Down Expand Up @@ -101,8 +100,8 @@ data CachedCabalFile = CachedCabalFile
deriving (Show)

-- | Cache ref that stores 'CachedCabalFile' per Cabal file.
cacheRef :: IORef (Map FilePath CachedCabalFile)
cacheRef = unsafePerformIO $ newIORef M.empty
cacheRef :: Cache FilePath CachedCabalFile
cacheRef = unsafePerformIO newCache
{-# NOINLINE cacheRef #-}

-- | Parse 'CabalInfo' from a @.cabal@ file at the given 'FilePath'.
Expand All @@ -118,7 +117,7 @@ parseCabalInfo ::
parseCabalInfo cabalFileAsGiven sourceFileAsGiven = liftIO $ do
cabalFile <- makeAbsolute cabalFileAsGiven
sourceFileAbs <- makeAbsolute sourceFileAsGiven
CachedCabalFile {..} <- withIORefCache cacheRef cabalFile $ do
CachedCabalFile {..} <- withCache cacheRef cabalFile $ do
cabalFileBs <- B.readFile cabalFile
genericPackageDescription <-
whenLeft (snd . runParseResult $ parseGenericPackageDescription cabalFileBs) $
Expand Down
11 changes: 4 additions & 7 deletions src/Ormolu/Utils/Fixity.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,18 +10,15 @@ where
import Control.Exception (throwIO)
import Control.Monad.IO.Class
import Data.Bifunctor (first)
import Data.IORef
import Data.List.NonEmpty (NonEmpty)
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.Text qualified as T
import Data.Text.IO.Utf8 qualified as T.Utf8
import Distribution.ModuleName (ModuleName)
import Distribution.Types.PackageName (PackageName)
import Ormolu.Exception
import Ormolu.Fixity
import Ormolu.Fixity.Parser
import Ormolu.Utils.IO (findClosestFileSatisfying, withIORefCache)
import Ormolu.Utils.IO (Cache, findClosestFileSatisfying, newCache, withCache)
import System.Directory
import System.IO.Unsafe (unsafePerformIO)
import Text.Megaparsec (errorBundlePretty)
Expand All @@ -37,7 +34,7 @@ getDotOrmoluForSourceFile ::
m (FixityOverrides, ModuleReexports)
getDotOrmoluForSourceFile sourceFile =
liftIO (findDotOrmoluFile sourceFile) >>= \case
Just dotOrmoluFile -> liftIO $ withIORefCache cacheRef dotOrmoluFile $ do
Just dotOrmoluFile -> liftIO $ withCache cacheRef dotOrmoluFile $ do
dotOrmoluRelative <- makeRelativeToCurrentDirectory dotOrmoluFile
contents <- T.Utf8.readFile dotOrmoluFile
case parseDotOrmolu dotOrmoluRelative contents of
Expand All @@ -58,8 +55,8 @@ findDotOrmoluFile = findClosestFileSatisfying $ \x ->
x == ".ormolu"

-- | Cache ref that maps names of @.ormolu@ files to their contents.
cacheRef :: IORef (Map FilePath (FixityOverrides, ModuleReexports))
cacheRef = unsafePerformIO (newIORef Map.empty)
cacheRef :: Cache FilePath (FixityOverrides, ModuleReexports)
cacheRef = unsafePerformIO newCache
{-# NOINLINE cacheRef #-}

-- | A wrapper around 'parseFixityDeclaration' for parsing individual fixity
Expand Down
22 changes: 16 additions & 6 deletions src/Ormolu/Utils/IO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,11 +3,14 @@

module Ormolu.Utils.IO
( findClosestFileSatisfying,
withIORefCache,
Cache,
newCache,
withCache,
)
where

import Control.Exception (catch, throwIO)
import Control.Monad (void)
import Control.Monad.IO.Class
import Data.IORef
import Data.Map.Lazy (Map)
Expand Down Expand Up @@ -48,14 +51,21 @@ findClosestFileSatisfying isRightFile rootOfSearch = liftIO $ do
then pure Nothing
else findClosestFileSatisfying isRightFile parentDir

newtype Cache k v = Cache (IORef (Map k v))

newCache :: (Ord k) => IO (Cache k v)
newCache = do
var <- newIORef mempty
pure (Cache var)

-- | Execute an 'IO' action but only if the given key is not found in the
-- 'IORef' cache.
withIORefCache :: (Ord k) => IORef (Map k v) -> k -> IO v -> IO v
withIORefCache cacheRef k action = do
cache <- readIORef cacheRef
-- cache.
withCache :: (Ord k) => Cache k v -> k -> IO v -> IO v
withCache (Cache cacheVar) k action = do
cache <- readIORef cacheVar
case M.lookup k cache of
Just v -> pure v
Nothing -> do
v <- action
modifyIORef' cacheRef (M.insert k v)
void $ atomicModifyIORef cacheVar (pure . M.insert k v)
pure v

0 comments on commit 392b2bc

Please sign in to comment.