This repository has been archived by the owner on Jan 2, 2021. It is now read-only.
-
Notifications
You must be signed in to change notification settings - Fork 96
/
Copy pathPreprocessor.hs
228 lines (200 loc) · 9.08 KB
/
Preprocessor.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0
module Development.IDE.Core.Preprocessor
( preprocessor
) where
import Development.IDE.GHC.CPP
import Development.IDE.GHC.Orphans()
import Development.IDE.GHC.Compat
import GhcMonad
import StringBuffer as SB
import Data.List.Extra
import System.FilePath
import System.IO.Extra
import Data.Char
import DynFlags
import qualified HeaderInfo as Hdr
import Development.IDE.Types.Diagnostics
import Development.IDE.Types.Location
import Development.IDE.GHC.Error
import SysTools (Option (..), runUnlit, runPp)
import Control.Monad.Trans.Except
import qualified GHC.LanguageExtensions as LangExt
import Data.Maybe
import Control.Exception.Safe (catch, throw)
import Data.IORef (IORef, modifyIORef, newIORef, readIORef)
import Data.Text (Text)
import qualified Data.Text as T
import Outputable (showSDoc)
import Control.DeepSeq (NFData(rnf))
import Control.Exception (evaluate)
import HscTypes (HscEnv(hsc_dflags))
-- | Given a file and some contents, apply any necessary preprocessors,
-- e.g. unlit/cpp. Return the resulting buffer and the DynFlags it implies.
preprocessor :: HscEnv -> FilePath -> Maybe StringBuffer -> ExceptT [FileDiagnostic] IO (StringBuffer, DynFlags)
preprocessor env filename mbContents = do
-- Perform unlit
(isOnDisk, contents) <-
if isLiterate filename then do
let dflags = hsc_dflags env
newcontent <- liftIO $ runLhs dflags filename mbContents
return (False, newcontent)
else do
contents <- liftIO $ maybe (hGetStringBuffer filename) return mbContents
let isOnDisk = isNothing mbContents
return (isOnDisk, contents)
-- Perform cpp
dflags <- ExceptT $ parsePragmasIntoDynFlags env filename contents
(isOnDisk, contents, dflags) <-
if not $ xopt LangExt.Cpp dflags then
return (isOnDisk, contents, dflags)
else do
cppLogs <- liftIO $ newIORef []
contents <- ExceptT
$ (Right <$> (runCpp dflags {log_action = logAction cppLogs} filename
$ if isOnDisk then Nothing else Just contents))
`catch`
( \(e :: GhcException) -> do
logs <- readIORef cppLogs
case diagsFromCPPLogs filename (reverse logs) of
[] -> throw e
diags -> return $ Left diags
)
dflags <- ExceptT $ parsePragmasIntoDynFlags env filename contents
return (False, contents, dflags)
-- Perform preprocessor
if not $ gopt Opt_Pp dflags then
return (contents, dflags)
else do
contents <- liftIO $ runPreprocessor dflags filename $ if isOnDisk then Nothing else Just contents
dflags <- ExceptT $ parsePragmasIntoDynFlags env filename contents
return (contents, dflags)
where
logAction :: IORef [CPPLog] -> LogAction
logAction cppLogs dflags _reason severity srcSpan _style msg = do
let log = CPPLog severity srcSpan $ T.pack $ showSDoc dflags msg
modifyIORef cppLogs (log :)
data CPPLog = CPPLog Severity SrcSpan Text
deriving (Show)
data CPPDiag
= CPPDiag
{ cdRange :: Range,
cdSeverity :: Maybe DiagnosticSeverity,
cdMessage :: [Text]
}
deriving (Show)
diagsFromCPPLogs :: FilePath -> [CPPLog] -> [FileDiagnostic]
diagsFromCPPLogs filename logs =
map (\d -> (toNormalizedFilePath' filename, ShowDiag, cppDiagToDiagnostic d)) $
go [] logs
where
-- On errors, CPP calls logAction with a real span for the initial log and
-- then additional informational logs with `UnhelpfulSpan`. Collect those
-- informational log messages and attaches them to the initial log message.
go :: [CPPDiag] -> [CPPLog] -> [CPPDiag]
go acc [] = reverse $ map (\d -> d {cdMessage = reverse $ cdMessage d}) acc
go acc (CPPLog sev (RealSrcSpan span) msg : logs) =
let diag = CPPDiag (realSrcSpanToRange span) (toDSeverity sev) [msg]
in go (diag : acc) logs
go (diag : diags) (CPPLog _sev (UnhelpfulSpan _) msg : logs) =
go (diag {cdMessage = msg : cdMessage diag} : diags) logs
go [] (CPPLog _sev (UnhelpfulSpan _) _msg : logs) = go [] logs
cppDiagToDiagnostic :: CPPDiag -> Diagnostic
cppDiagToDiagnostic d =
Diagnostic
{ _range = cdRange d,
_severity = cdSeverity d,
_code = Nothing,
_source = Just "CPP",
_message = T.unlines $ cdMessage d,
_relatedInformation = Nothing,
_tags = Nothing
}
isLiterate :: FilePath -> Bool
isLiterate x = takeExtension x `elem` [".lhs",".lhs-boot"]
-- | This reads the pragma information directly from the provided buffer.
parsePragmasIntoDynFlags
:: HscEnv
-> FilePath
-> SB.StringBuffer
-> IO (Either [FileDiagnostic] DynFlags)
parsePragmasIntoDynFlags env fp contents = catchSrcErrors dflags0 "pragmas" $ do
let opts = Hdr.getOptions dflags0 contents fp
-- Force bits that might keep the dflags and stringBuffer alive unnecessarily
evaluate $ rnf opts
(dflags, _, _) <- parseDynamicFilePragma dflags0 opts
dflags' <- initializePlugins env dflags
return $ disableWarningsAsErrors dflags'
where dflags0 = hsc_dflags env
-- | Run (unlit) literate haskell preprocessor on a file, or buffer if set
runLhs :: DynFlags -> FilePath -> Maybe SB.StringBuffer -> IO SB.StringBuffer
runLhs dflags filename contents = withTempDir $ \dir -> do
let fout = dir </> takeFileName filename <.> "unlit"
filesrc <- case contents of
Nothing -> return filename
Just cnts -> do
let fsrc = dir </> takeFileName filename <.> "literate"
withBinaryFile fsrc WriteMode $ \h ->
hPutStringBuffer h cnts
return fsrc
unlit filesrc fout
SB.hGetStringBuffer fout
where
unlit filein fileout = SysTools.runUnlit dflags (args filein fileout)
args filein fileout = [
SysTools.Option "-h"
, SysTools.Option (escape filename) -- name this file
, SysTools.FileOption "" filein -- input file
, SysTools.FileOption "" fileout ] -- output file
-- taken from ghc's DriverPipeline.hs
escape ('\\':cs) = '\\':'\\': escape cs
escape ('\"':cs) = '\\':'\"': escape cs
escape ('\'':cs) = '\\':'\'': escape cs
escape (c:cs) = c : escape cs
escape [] = []
-- | Run CPP on a file
runCpp :: DynFlags -> FilePath -> Maybe SB.StringBuffer -> IO SB.StringBuffer
runCpp dflags filename contents = withTempDir $ \dir -> do
let out = dir </> takeFileName filename <.> "out"
dflags <- pure $ addOptP "-D__GHCIDE__" dflags
case contents of
Nothing -> do
-- Happy case, file is not modified, so run CPP on it in-place
-- which also makes things like relative #include files work
-- and means location information is correct
doCpp dflags True filename out
liftIO $ SB.hGetStringBuffer out
Just contents -> do
-- Sad path, we have to create a version of the path in a temp dir
-- __FILE__ macro is wrong, ignoring that for now (likely not a real issue)
-- Relative includes aren't going to work, so we fix that by adding to the include path.
dflags <- return $ addIncludePathsQuote (takeDirectory filename) dflags
-- Location information is wrong, so we fix that by patching it afterwards.
let inp = dir </> "___GHCIDE_MAGIC___"
withBinaryFile inp WriteMode $ \h ->
hPutStringBuffer h contents
doCpp dflags True inp out
-- Fix up the filename in lines like:
-- # 1 "C:/Temp/extra-dir-914611385186/___GHCIDE_MAGIC___"
let tweak x
| Just x <- stripPrefix "# " x
, "___GHCIDE_MAGIC___" `isInfixOf` x
, let num = takeWhile (not . isSpace) x
-- important to use /, and never \ for paths, even on Windows, since then C escapes them
-- and GHC gets all confused
= "# " <> num <> " \"" <> map (\x -> if isPathSeparator x then '/' else x) filename <> "\""
| otherwise = x
stringToStringBuffer . unlines . map tweak . lines <$> readFileUTF8' out
-- | Run a preprocessor on a file
runPreprocessor :: DynFlags -> FilePath -> Maybe SB.StringBuffer -> IO SB.StringBuffer
runPreprocessor dflags filename contents = withTempDir $ \dir -> do
let out = dir </> takeFileName filename <.> "out"
inp <- case contents of
Nothing -> return filename
Just contents -> do
let inp = dir </> takeFileName filename <.> "hs"
withBinaryFile inp WriteMode $ \h ->
hPutStringBuffer h contents
return inp
runPp dflags [SysTools.Option filename, SysTools.Option inp, SysTools.FileOption "" out]
SB.hGetStringBuffer out