{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Plugin.GhcTags ( plugin ) where
import Control.Concurrent
import Control.Exception
import qualified Data.ByteString as BS
import Data.ByteString.Builder (Builder)
import qualified Data.ByteString.Builder as BS
import Data.Functor ((<$))
import Data.List (sort)
import qualified Data.Map as Map
import Data.Maybe (mapMaybe)
import System.IO
import System.IO.Error (tryIOError)
import System.IO.Unsafe (unsafePerformIO)
import System.Directory
import GhcPlugins ( CommandLineOption
, Hsc
, HsParsedModule (..)
, ModSummary
, Plugin (..)
, liftIO
, purePlugin
)
import GhcPlugins hiding (occName, (<>))
import HsExtension (GhcPs)
import HsSyn (HsModule)
import Plugin.GhcTags.Generate
import Plugin.GhcTags.Parser
tagsMVar :: MVar (Maybe TagsMap)
tagsMVar = unsafePerformIO $ newMVar Nothing
plugin :: Plugin
plugin = GhcPlugins.defaultPlugin {
parsedResultAction = ghcTagPlugin,
pluginRecompile = purePlugin
}
ghcTagPlugin :: [CommandLineOption] -> ModSummary -> HsParsedModule -> Hsc HsParsedModule
ghcTagPlugin options _modSummary hsParsedModule@HsParsedModule {hpm_module} =
hsParsedModule <$ liftIO (updateTags tagsFile hpm_module)
where
tagsFile :: FilePath
tagsFile = case options of
[] -> "tags"
a : _ -> a
updateTags :: FilePath
-> Located (HsModule GhcPs)
-> IO ()
updateTags tagsFile lmodule =
mvarLock tagsMVar $ \mTagsMap -> do
(tagsMap :: TagsMap) <-
case mTagsMap of
Nothing -> do
a <- doesFileExist tagsFile
res <-
if a
then do
mbytes <- tryIOError (BS.readFile tagsFile)
case mbytes of
Left err -> do
putStrLn $ "GhcTags: error reading \"" ++ tagsFile ++ "\": " ++ (show err)
return $ Right []
Right bytes ->
parseVimTagFile bytes
else return $ Right []
case res of
Left err -> do
putStrLn $ "GhcTags: error reading or parsing \"" ++ tagsFile ++ "\": " ++ err
return $ Map.empty
Right tagList -> do
return $ mkTagsMap tagList
Just tagsMap -> return tagsMap
let tagsMap', updatedTagsMap :: TagsMap
tagsMap' =
mkTagsMap
$ mapMaybe ghcTagToTag
$ generateTagsForModule
$ lmodule
updatedTagsMap = tagsMap' `Map.union` tagsMap
withFile tagsFile WriteMode $ \fhandle ->
BS.hPutBuilder fhandle
$ foldMap formatVimTag
$ sort
$ concat
$ Map.elems updatedTagsMap
return $ updatedTagsMap `seq` Just updatedTagsMap
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'
ghcTagToTag :: GhcTag -> Maybe Tag
ghcTagToTag GhcTag { tagSrcSpan, tagTag } =
case tagSrcSpan of
UnhelpfulSpan {} -> Nothing
RealSrcSpan realSrcSpan ->
Just $ Tag { tagName = TagName (fs_bs tagTag)
, tagFile = TagFile (fs_bs (srcSpanFile realSrcSpan))
, tagLine = srcSpanStartLine realSrcSpan
}
formatVimTag :: Tag -> Builder
formatVimTag Tag { tagName, tagFile, tagLine } =
BS.byteString (getTagName tagName)
<> BS.charUtf8 '\t'
<> BS.byteString (getTagFile tagFile)
<> BS.charUtf8 '\t'
<> BS.intDec tagLine
<> BS.charUtf8 '\n'