{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
module Plugin.GhcTags ( plugin, Options (..) ) where
import Control.Exception
import Control.Monad.State.Strict
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BSC
import qualified Data.ByteString.Lazy as BSL
import qualified Data.ByteString.Builder as BB
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
#if __GLASGOW_HASKELL__ < 808
import Data.Functor (void, (<$))
#endif
import Data.Functor.Identity (Identity (..))
import Data.List (sortBy)
import Data.Foldable (traverse_)
import Data.Maybe (mapMaybe)
import System.Directory
import System.FilePath
import System.FilePath.ByteString (RawFilePath)
import qualified System.FilePath.ByteString as FilePath
import System.IO
#if !defined(mingw32_HOST_OS)
import Foreign.C.Types (CInt (..))
import Foreign.C.Error (throwErrnoIfMinus1_)
import System.Posix.Types (Fd (..))
import System.Posix.IO (handleToFd)
#endif
import Options.Applicative.Types (ParserFailure (..))
import qualified Pipes as Pipes
import Pipes.Safe (SafeT)
import qualified Pipes.Safe as Pipes.Safe
import qualified Pipes.ByteString as Pipes.BS
import GhcPlugins ( CommandLineOption
, DynFlags
, Hsc
, HsParsedModule (..)
, Located
, Module
, ModSummary (..)
, ModLocation (..)
, Plugin (..)
)
import qualified GhcPlugins
import HsExtension (GhcPs)
import HsSyn (HsModule (..))
import Outputable (($+$), ($$))
import qualified Outputable as Out
import qualified PprColour
import GhcTags.Ghc
import GhcTags.Tag
import GhcTags.Stream
import qualified GhcTags.CTag as CTag
import qualified GhcTags.ETag as ETag
import Plugin.GhcTags.Options
import Plugin.GhcTags.FileLock
import qualified Plugin.GhcTags.CTag as CTag
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@ModSummary {ms_mod, ms_hspp_opts = dynFlags}
hsParsedModule@HsParsedModule {hpm_module} =
hsParsedModule <$
case runOptionParser options of
Success opts@Options { filePath = Identity tagsFile
, debug
} ->
GhcPlugins.liftIO $ do
let sourceFile = case splitFileName tagsFile of
(dir, name) -> dir </> "." ++ name
lockFile = sourceFile ++ ".lock"
handle (\ioerr -> do
putDocLn dynFlags (messageDoc UnhandledException ms_mod (displayException ioerr))
throwIO $ GhcTagsPluginIOExceptino ioerr) $
flip finally (void $ try @IOException $ removeFile sourceFile) $
withFileLock lockFile ExclusiveLock WriteMode $ \_ -> do
mbInSize <-
if debug
then Just <$> getFileSize tagsFile
`catch` \(_ :: IOException) -> pure 0
else pure Nothing
updateTags opts moduleSummary hpm_module sourceFile
when debug $ do
let Just inSize = mbInSize
outSize <- getFileSize tagsFile
when (inSize > outSize)
$ throwIO (userError $ concat
[ "tags file '"
, tagsFile
, "' size shrinked: "
, show inSize
, "→"
, show outSize
])
Failure (ParserFailure f) ->
GhcPlugins.liftIO $
putDocLn dynFlags
(messageDoc
OptionParserFailure
ms_mod
(show (case f "<ghc-tags-plugin>" of (h, _, _) -> h)
++ " " ++ show options))
CompletionInvoked {} -> error "ghc-tags-plugin: impossible happend"
data MessageType =
ReadException
| ParserException
| WriteException
| UnhandledException
| OptionParserFailure
| DebugMessage
instance Show MessageType where
show ReadException = "read error"
show ParserException = "tags parser error"
show WriteException = "write error"
show UnhandledException = "unhandled error"
show OptionParserFailure = "plugin options parser error"
show DebugMessage = ""
updateTags :: Options Identity
-> ModSummary
-> Located (HsModule GhcPs)
-> FilePath
-> IO ()
updateTags Options { etags, filePath = Identity tagsFile, debug }
ModSummary {ms_mod, ms_location, ms_hspp_opts = dynFlags}
lmodule sourceFile = do
tagsFileExists <- doesFileExist tagsFile
when tagsFileExists
$ renameFile tagsFile sourceFile
withFile tagsFile WriteMode $ \writeHandle ->
withFile sourceFile ReadWriteMode $ \readHandle -> do
cwd <- BSC.pack <$> getCurrentDirectory
tagsDir <- BSC.pack <$> canonicalizePath (fst $ splitFileName tagsFile)
case (etags, ml_hs_file ms_location) of
(False, Nothing) -> pure ()
(False, Just sourcePath) -> do
let sourcePathBS = Text.encodeUtf8 (Text.pack sourcePath)
producer :: Pipes.Producer ByteString (SafeT IO) ()
producer
| tagsFileExists =
void (Pipes.BS.fromHandle readHandle)
`Pipes.Safe.catchP` \(e :: IOException) ->
Pipes.lift $ Pipes.liftIO $
putDocLn dynFlags (messageDoc ReadException ms_mod (displayException e))
| otherwise = pure ()
pipe :: Pipes.Effect (StateT Int (StateT [CTag] (SafeT IO))) ()
pipe =
Pipes.for
(Pipes.hoist Pipes.lift $ Pipes.hoist Pipes.lift (tagParser (either (const Nothing) Just <$> CTag.parseTagLine) producer)
`Pipes.Safe.catchP` \(e :: IOException) ->
Pipes.lift $ Pipes.liftIO $
putDocLn dynFlags $ messageDoc ParserException ms_mod (displayException e)
)
$
(\tag -> do
modify' succ
Pipes.hoist Pipes.lift $
runCombineTagsPipe writeHandle
CTag.compareTags
CTag.formatTag
(fixFilePath cwd tagsDir sourcePathBS)
tag
`Pipes.Safe.catchP` \(e :: IOException) ->
Pipes.lift $ Pipes.liftIO $
putDocLn dynFlags $ messageDoc WriteException ms_mod (displayException e)
)
let tags :: [CTag]
tags = map (fixTagFilePath cwd tagsDir)
. sortBy compareTags
. mapMaybe (ghcTagToTag SingCTag dynFlags)
. getGhcTags
$ lmodule
BSL.hPut writeHandle (BB.toLazyByteString (foldMap CTag.formatHeader CTag.headers))
(parsedTags, tags') <- Pipes.Safe.runSafeT $ runStateT (execStateT (Pipes.runEffect pipe) 0) tags
traverse_ (BSL.hPut writeHandle . BB.toLazyByteString . CTag.formatTag) tags'
hFlush writeHandle
hDataSync writeHandle
when debug
$ printMessageDoc dynFlags DebugMessage ms_mod
(concat [ "parsed: "
, show parsedTags
, " found: "
, show (length tags)
, " left: "
, show (length tags')
])
(True, Nothing) -> pure ()
(True, Just sourcePath) ->
try @IOException (BS.hGetContents readHandle)
>>= \case
Left err ->
putDocLn dynFlags $ messageDoc ReadException ms_mod (displayException err)
Right txt -> do
pres <- try @IOException $ ETag.parseTagsFile txt
case pres of
Left err ->
putDocLn dynFlags $ messageDoc ParserException ms_mod (displayException err)
Right (Left err) ->
printMessageDoc dynFlags ParserException ms_mod err
Right (Right tags) -> do
ll <- map (succ . BS.length) . BSC.lines <$> BS.readFile sourcePath
let sourcePathBS = Text.encodeUtf8 (Text.pack sourcePath)
newTags :: [ETag]
newTags =
(sortBy ETag.compareTags
. map ( ETag.withByteOffset ll
. fixTagFilePath cwd tagsDir
)
. mapMaybe (ghcTagToTag SingETag dynFlags)
. getGhcTags
$ lmodule)
tags' :: [ETag]
tags' = combineTags
ETag.compareTags
(fixFilePath cwd tagsDir sourcePathBS)
newTags
(sortBy ETag.compareTags tags)
when debug
$ printMessageDoc dynFlags DebugMessage ms_mod
(concat [ "parsed: "
, show (length tags)
, " found: "
, show (length newTags)
])
BB.hPutBuilder writeHandle (ETag.formatETagsFile tags')
where
fixFilePath :: RawFilePath
-> RawFilePath
-> RawFilePath -> RawFilePath
fixFilePath cwd tagsDir =
FilePath.normalise
. FilePath.makeRelative tagsDir
. (cwd FilePath.</>)
fixTagFilePath :: RawFilePath -> RawFilePath -> Tag tk -> Tag tk
fixTagFilePath cwd tagsDir tag@Tag { tagFilePath = TagFilePath fp } =
tag { tagFilePath =
TagFilePath
(Text.decodeUtf8
(fixFilePath cwd tagsDir
(Text.encodeUtf8 fp)))
}
data MessageSeverity
= Debug
| Warning
| Error
messageDoc :: MessageType -> Module -> String -> Out.SDoc
messageDoc errorType mod_ errorMessage =
Out.blankLine
$+$
Out.coloured PprColour.colBold
((Out.text "GhcTagsPlugin: ")
Out.<> (Out.coloured messageColour (Out.text $ show errorType)))
$$
Out.coloured PprColour.colBold (Out.nest 4 $ Out.ppr mod_)
$$
(Out.nest 8 $ Out.coloured messageColour (Out.text errorMessage))
$+$
Out.blankLine
$+$ case severity of
Error ->
Out.coloured PprColour.colBold (Out.text "Please report this bug to: ")
Out.<> Out.text "https://github.com/coot/ghc-tags-plugin/issues"
$+$ Out.blankLine
Warning -> Out.blankLine
Debug -> Out.blankLine
where
severity = case errorType of
ReadException -> Error
ParserException -> Error
WriteException -> Error
UnhandledException -> Error
OptionParserFailure -> Warning
DebugMessage -> Debug
messageColour = case severity of
Error -> PprColour.colRedFg
Warning -> PprColour.colBlueFg
Debug -> PprColour.colCyanFg
putDocLn :: DynFlags -> Out.SDoc -> IO ()
putDocLn dynFlags sdoc =
putStrLn $
Out.renderWithStyle
dynFlags
sdoc
(Out.setStyleColoured True $ Out.defaultErrStyle dynFlags)
printMessageDoc :: DynFlags -> MessageType -> Module -> String -> IO ()
printMessageDoc dynFlags = (fmap . fmap . fmap) (putDocLn dynFlags) messageDoc
#if !defined(mingw32_HOST_OS)
hDataSync :: Handle -> IO ()
hDataSync h = do
fd <- handleToFd h
throwErrnoIfMinus1_ "ghc-tags-plugin" (c_fdatasync fd)
foreign import ccall safe "fdatasync"
c_fdatasync :: Fd -> IO CInt
#else
hDataSync :: Handle -> IO ()
hDataSync _ = pure ()
#endif