{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Plugin.GhcTags ( plugin ) where
import Control.Concurrent
import Control.Exception
import qualified Data.ByteString as BS
import qualified Data.ByteString.Builder as BS
#if __GLASGOW_HASKELL__ < 808
import Data.Functor ((<$))
#endif
import Data.List (sortBy)
import qualified Data.Map as Map
import Data.Maybe (mapMaybe)
import System.Directory
import System.FilePath
import System.IO
import System.IO.Error (tryIOError)
import System.IO.Unsafe (unsafePerformIO)
import qualified Data.Text.Encoding as Text
import GhcPlugins ( CommandLineOption
, Hsc
, HsParsedModule (..)
, Located
, ModSummary
, Plugin (..)
)
import qualified GhcPlugins
import HsExtension (GhcPs)
import HsSyn (HsModule)
import Plugin.GhcTags.Generate
import Plugin.GhcTags.Tag
import qualified Plugin.GhcTags.Vim as Vim
tagsMVar :: MVar (Maybe TagsMap)
tagsMVar = unsafePerformIO $ newMVar Nothing
plugin :: Plugin
plugin = GhcPlugins.defaultPlugin {
parsedResultAction = ghcTagsPlugin,
pluginRecompile = GhcPlugins.purePlugin
}
data GhcTagsPluginException =
GhcTagsPluginIOExceptino IOException
deriving Show
instance Exception GhcTagsPluginException
ghcTagsPlugin :: [CommandLineOption] -> ModSummary -> HsParsedModule -> Hsc HsParsedModule
ghcTagsPlugin options _modSummary hsParsedModule@HsParsedModule {hpm_module} =
hsParsedModule <$ GhcPlugins.liftIO (updateTags tagsFile hpm_module)
where
tagsFile :: FilePath
tagsFile = case options of
[] -> "tags"
a : _ -> a
updateTags :: FilePath
-> Located (HsModule GhcPs)
-> IO ()
updateTags tagsFile lmodule =
handle (throwIO . GhcTagsPluginIOExceptino) $
mvarLock tagsMVar $ \mTagsMap -> do
(tagsMap :: TagsMap) <-
case mTagsMap of
Just tagsMap -> return tagsMap
Nothing -> do
a <- doesFileExist tagsFile
res <-
if a
then do
mtext <- tryIOError (Text.decodeUtf8 <$> BS.readFile tagsFile)
case mtext of
Left err -> do
putStrLn $ "GhcTags: error reading \"" ++ tagsFile ++ "\": " ++ (show err)
pure $ Right []
Right txt ->
Vim.parseTagsFile txt
else pure $ Right []
case res of
Left err -> do
putStrLn $ "GhcTags: error reading or parsing \"" ++ tagsFile ++ "\": " ++ err
return $ Map.empty
Right tagList -> do
return $ mkTagsMap tagList
cwd <- getCurrentDirectory
tagsDir <- canonicalizePath (fst $ splitFileName tagsFile)
let tagsMap' :: TagsMap
tagsMap' =
(mkTagsMap
. map (fixFileName cwd tagsDir)
. mapMaybe ghcTagToTag
. getGhcTags
$ lmodule)
`Map.union`
tagsMap
withFile tagsFile WriteMode
$ flip BS.hPutBuilder
( Vim.formatTagsFile
. sortBy compareTags
. concat
. Map.elems
$ tagsMap'
)
pure (Just tagsMap')
where
fixFileName :: FilePath -> FilePath -> Tag -> Tag
fixFileName cwd tagsDir tag@Tag { tagFile = TagFile path } =
tag { tagFile = TagFile (makeRelative tagsDir (cwd </> path)) }
mvarLock :: MVar a
-> (a -> IO a)
-> IO ()
mvarLock v k = mask $ \unmask -> do
a <- takeMVar v
a' <- unmask (k a)
`onException`
putMVar v a
putMVar v $! a'