{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Plugin.GhcTags ( plugin ) where
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 Data.Maybe (mapMaybe)
import qualified Data.Text.Encoding as Text
import System.Directory
import System.FilePath
import System.IO
import System.IO.Error (tryIOError)
import System.FileLock ( SharedExclusive (..)
, withFileLock)
import GhcPlugins ( CommandLineOption
, Hsc
, HsParsedModule (..)
, Located
, ModSummary (..)
, Plugin (..)
)
import qualified GhcPlugins
import HsExtension (GhcPs)
import HsSyn (HsModule (..))
import qualified Outputable as Out
import qualified PprColour
import Plugin.GhcTags.Generate
import Plugin.GhcTags.Tag
import qualified Plugin.GhcTags.Vim as Vim
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 moduleSummary hsParsedModule@HsParsedModule {hpm_module} =
hsParsedModule <$ GhcPlugins.liftIO (updateTags moduleSummary tagsFile hpm_module)
where
tagsFile :: FilePath
tagsFile = case options of
[] -> "tags"
a : _ -> a
updateTags :: ModSummary
-> FilePath
-> Located (HsModule GhcPs)
-> IO ()
updateTags ModSummary {ms_mod, ms_hspp_opts = dynFlags} tagsFile lmodule =
handle (throwIO . GhcTagsPluginIOExceptino) $
withFileLock tagsFile Exclusive $ \_ -> do
a <- doesFileExist tagsFile
tags <-
if a
then do
res <- tryIOError $
Text.decodeUtf8 <$> BS.readFile tagsFile
>>= Vim.parseTagsFile
case res of
Left err -> do
putDocLn (errorDoc $ displayException err)
pure []
Right (Left err) -> do
putDocLn (errorDoc err)
pure []
Right (Right tags) ->
pure tags
else pure []
cwd <- getCurrentDirectory
tagsDir <- canonicalizePath (fst $ splitFileName tagsFile)
let tags' :: [Tag]
tags' =
( map (fixFileName cwd tagsDir)
. sortBy compareTags
. mapMaybe ghcTagToTag
. getGhcTags
$ lmodule)
`combineTags`
tags
withFile tagsFile WriteMode $ \h ->
BS.hPutBuilder h (Vim.formatTagsFile tags')
where
fixFileName :: FilePath -> FilePath -> Tag -> Tag
fixFileName cwd tagsDir tag@Tag { tagFile = TagFile path } =
tag { tagFile = TagFile (makeRelative tagsDir (cwd </> path)) }
errorDoc :: String -> Out.SDoc
errorDoc errorMessage =
Out.coloured PprColour.colBold
$ Out.blankLine
Out.$+$
((Out.text "GhcTagsPlugin: ")
Out.<> (Out.coloured PprColour.colRedFg (Out.text "error:")))
Out.$$
(Out.nest 4 $ Out.ppr ms_mod)
Out.$$
(Out.nest 8 $ Out.coloured PprColour.colRedFg (Out.text errorMessage))
Out.$+$
Out.blankLine
putDocLn :: Out.SDoc -> IO ()
putDocLn sdoc =
putStrLn $
Out.renderWithStyle
dynFlags
sdoc
(Out.setStyleColoured True $ Out.defaultErrStyle dynFlags)