Apply inline config to module header (fixes #151)

pull/153/head
Lennart Spitzner 2018-06-04 16:57:07 +02:00
parent bdee27cb59
commit 57c48f64c1
3 changed files with 30 additions and 28 deletions

View File

@ -248,7 +248,7 @@ coreIO putErrorLnIO config suppressOutput inputPathM outputPathM = ExceptT.runEx
putErrorLn $ show left putErrorLn $ show left
ExceptT.throwE 60 ExceptT.throwE 60
Right (anns, parsedSource, hasCPP) -> do Right (anns, parsedSource, hasCPP) -> do
inlineConf <- case extractCommentConfigs anns (getTopLevelDeclNameMap parsedSource) of (inlineConf, perItemConf) <- case extractCommentConfigs anns (getTopLevelDeclNameMap parsedSource) of
Left (err, input) -> do Left (err, input) -> do
putErrorLn putErrorLn
$ "Error: parse error in inline configuration:" $ "Error: parse error in inline configuration:"
@ -257,6 +257,7 @@ coreIO putErrorLnIO config suppressOutput inputPathM outputPathM = ExceptT.runEx
ExceptT.throwE 61 ExceptT.throwE 61
Right c -> -- trace (showTree c) $ Right c -> -- trace (showTree c) $
pure c pure c
let moduleConf = cZipWith fromOptionIdentity config inlineConf
when (config & _conf_debug .> _dconf_dump_ast_full .> confUnpack) $ do when (config & _conf_debug .> _dconf_dump_ast_full .> confUnpack) $ do
let val = printTreeWithCustom 100 (customLayouterF anns) parsedSource let val = printTreeWithCustom 100 (customLayouterF anns) parsedSource
trace ("---- ast ----\n" ++ show val) $ return () trace ("---- ast ----\n" ++ show val) $ return ()
@ -265,15 +266,15 @@ coreIO putErrorLnIO config suppressOutput inputPathM outputPathM = ExceptT.runEx
then do then do
pure ([], Text.pack $ ExactPrint.exactPrint parsedSource anns) pure ([], Text.pack $ ExactPrint.exactPrint parsedSource anns)
else do else do
let omitCheck = config & _conf_errorHandling .> _econf_omit_output_valid_check .> confUnpack let omitCheck = moduleConf & _conf_errorHandling .> _econf_omit_output_valid_check .> confUnpack
(ews, outRaw) <- if hasCPP || omitCheck (ews, outRaw) <- if hasCPP || omitCheck
then return $ pPrintModule config inlineConf anns parsedSource then return $ pPrintModule moduleConf perItemConf anns parsedSource
else liftIO $ pPrintModuleAndCheck config inlineConf anns parsedSource else liftIO $ pPrintModuleAndCheck moduleConf perItemConf anns parsedSource
let hackF s = fromMaybe s $ TextL.stripPrefix (TextL.pack "-- BRITANY_INCLUDE_HACK ") s let hackF s = fromMaybe s $ TextL.stripPrefix (TextL.pack "-- BRITANY_INCLUDE_HACK ") s
let out = TextL.toStrict $ if hackAroundIncludes let out = TextL.toStrict $ if hackAroundIncludes
then TextL.intercalate (TextL.pack "\n") $ fmap hackF $ TextL.splitOn (TextL.pack "\n") outRaw then TextL.intercalate (TextL.pack "\n") $ fmap hackF $ TextL.splitOn (TextL.pack "\n") outRaw
else outRaw else outRaw
out' <- if config & _conf_obfuscate & confUnpack out' <- if moduleConf & _conf_obfuscate & confUnpack
then lift $ obfuscate out then lift $ obfuscate out
else pure out else pure out
pure $ (ews, out') pure $ (ews, out')

View File

@ -71,7 +71,7 @@ data InlineConfigTarget
extractCommentConfigs extractCommentConfigs
:: ExactPrint.Anns :: ExactPrint.Anns
-> TopLevelDeclNameMap -> TopLevelDeclNameMap
-> Either (String, String) InlineConfig -> Either (String, String) (CConfig Option, PerItemConfig)
extractCommentConfigs anns (TopLevelDeclNameMap declNameMap) = do extractCommentConfigs anns (TopLevelDeclNameMap declNameMap) = do
let let
commentLiness = commentLiness =
@ -200,11 +200,10 @@ extractCommentConfigs anns (TopLevelDeclNameMap declNameMap) = do
_ -> False _ -> False
] ]
pure $ InlineConfig pure
{ _icd_perModule = perModule $ ( perModule
, _icd_perBinding = perBinding , PerItemConfig { _icd_perBinding = perBinding, _icd_perKey = perKey }
, _icd_perKey = perKey )
}
getTopLevelDeclNameMap :: GHC.ParsedSource -> TopLevelDeclNameMap getTopLevelDeclNameMap :: GHC.ParsedSource -> TopLevelDeclNameMap
@ -256,17 +255,19 @@ parsePrintModule configWithDebugs inputText = runExceptT $ do
case parseResult of case parseResult of
Left err -> throwE [ErrorInput err] Left err -> throwE [ErrorInput err]
Right x -> pure x Right x -> pure x
inlineConf <- either (throwE . (: []) . uncurry ErrorMacroConfig) pure (inlineConf, perItemConf) <-
either (throwE . (: []) . uncurry ErrorMacroConfig) pure
$ extractCommentConfigs anns (getTopLevelDeclNameMap parsedSource) $ extractCommentConfigs anns (getTopLevelDeclNameMap parsedSource)
let moduleConfig = cZipWith fromOptionIdentity config inlineConf
(errsWarns, outputTextL) <- do (errsWarns, outputTextL) <- do
let omitCheck = let omitCheck =
config moduleConfig
& _conf_errorHandling & _conf_errorHandling
& _econf_omit_output_valid_check & _econf_omit_output_valid_check
& confUnpack & confUnpack
(ews, outRaw) <- if hasCPP || omitCheck (ews, outRaw) <- if hasCPP || omitCheck
then return $ pPrintModule config inlineConf anns parsedSource then return $ pPrintModule moduleConfig perItemConf anns parsedSource
else lift $ pPrintModuleAndCheck config inlineConf anns parsedSource else lift $ pPrintModuleAndCheck moduleConfig perItemConf anns parsedSource
let hackF s = fromMaybe s let hackF s = fromMaybe s
$ TextL.stripPrefix (TextL.pack "-- BRITANY_INCLUDE_HACK ") s $ TextL.stripPrefix (TextL.pack "-- BRITANY_INCLUDE_HACK ") s
pure $ if hackAroundIncludes pure $ if hackAroundIncludes
@ -284,7 +285,7 @@ parsePrintModule configWithDebugs inputText = runExceptT $ do
customErrOrder ErrorUnknownNode{} = 3 customErrOrder ErrorUnknownNode{} = 3
customErrOrder ErrorMacroConfig{} = 5 customErrOrder ErrorMacroConfig{} = 5
let hasErrors = let hasErrors =
case config & _conf_errorHandling & _econf_Werror & confUnpack of case moduleConfig & _conf_errorHandling & _econf_Werror & confUnpack of
False -> 0 < maximum (-1 : fmap customErrOrder errsWarns) False -> 0 < maximum (-1 : fmap customErrOrder errsWarns)
True -> not $ null errsWarns True -> not $ null errsWarns
if hasErrors then throwE $ errsWarns else pure $ TextL.toStrict outputTextL if hasErrors then throwE $ errsWarns else pure $ TextL.toStrict outputTextL
@ -297,7 +298,7 @@ parsePrintModule configWithDebugs inputText = runExceptT $ do
-- can occur. -- can occur.
pPrintModule pPrintModule
:: Config :: Config
-> InlineConfig -> PerItemConfig
-> ExactPrint.Anns -> ExactPrint.Anns
-> GHC.ParsedSource -> GHC.ParsedSource
-> ([BrittanyError], TextL.Text) -> ([BrittanyError], TextL.Text)
@ -335,7 +336,7 @@ pPrintModule conf inlineConf anns parsedModule =
-- if it does not. -- if it does not.
pPrintModuleAndCheck pPrintModuleAndCheck
:: Config :: Config
-> InlineConfig -> PerItemConfig
-> ExactPrint.Anns -> ExactPrint.Anns
-> GHC.ParsedSource -> GHC.ParsedSource
-> IO ([BrittanyError], TextL.Text) -> IO ([BrittanyError], TextL.Text)
@ -361,18 +362,20 @@ parsePrintModuleTests conf filename input = do
case parseResult of case parseResult of
Left (_ , s ) -> return $ Left $ "parsing error: " ++ s Left (_ , s ) -> return $ Left $ "parsing error: " ++ s
Right (anns, parsedModule) -> runExceptT $ do Right (anns, parsedModule) -> runExceptT $ do
inlineConf <- (inlineConf, perItemConf) <-
case extractCommentConfigs anns (getTopLevelDeclNameMap parsedModule) of case extractCommentConfigs anns (getTopLevelDeclNameMap parsedModule) of
Left err -> throwE $ "error in inline config: " ++ show err Left err -> throwE $ "error in inline config: " ++ show err
Right x -> pure x Right x -> pure x
let moduleConf = cZipWith fromOptionIdentity conf inlineConf
let omitCheck = let omitCheck =
conf conf
& _conf_errorHandling & _conf_errorHandling
.> _econf_omit_output_valid_check .> _econf_omit_output_valid_check
.> confUnpack .> confUnpack
(errs, ltext) <- if omitCheck (errs, ltext) <- if omitCheck
then return $ pPrintModule conf inlineConf anns parsedModule then return $ pPrintModule moduleConf perItemConf anns parsedModule
else lift $ pPrintModuleAndCheck conf inlineConf anns parsedModule else
lift $ pPrintModuleAndCheck moduleConf perItemConf anns parsedModule
if null errs if null errs
then pure $ TextL.toStrict $ ltext then pure $ TextL.toStrict $ ltext
else else
@ -434,7 +437,6 @@ ppModule lmod@(L _loc _m@(HsModule _name _exports _ decls _ _)) = do
let declAnnKey = ExactPrint.mkAnnKey decl let declAnnKey = ExactPrint.mkAnnKey decl
let declBindingNames = getDeclBindingNames decl let declBindingNames = getDeclBindingNames decl
inlineConf <- mAsk inlineConf <- mAsk
let inlineModConf = _icd_perModule inlineConf
let mDeclConf = Map.lookup declAnnKey $ _icd_perKey inlineConf let mDeclConf = Map.lookup declAnnKey $ _icd_perKey inlineConf
let mBindingConfs = let mBindingConfs =
declBindingNames <&> \n -> Map.lookup n $ _icd_perBinding inlineConf declBindingNames <&> \n -> Map.lookup n $ _icd_perBinding inlineConf
@ -448,7 +450,7 @@ ppModule lmod@(L _loc _m@(HsModule _name _exports _ decls _ _)) = do
config <- mAsk config <- mAsk
let config' = cZipWith fromOptionIdentity config $ mconcat let config' = cZipWith fromOptionIdentity config $ mconcat
(inlineModConf : (catMaybes (mBindingConfs ++ [mDeclConf]))) (catMaybes (mBindingConfs ++ [mDeclConf]))
let exactprintOnly = config' & _conf_roundtrip_exactprint_only & confUnpack let exactprintOnly = config' & _conf_roundtrip_exactprint_only & confUnpack
toLocal config' filteredAnns $ do toLocal config' filteredAnns $ do

View File

@ -28,9 +28,8 @@ import Data.Generics.Uniplate.Direct as Uniplate
data InlineConfig = InlineConfig data PerItemConfig = PerItemConfig
{ _icd_perModule :: CConfig Option { _icd_perBinding :: Map String (CConfig Option)
, _icd_perBinding :: Map String (CConfig Option)
, _icd_perKey :: Map ExactPrint.Types.AnnKey (CConfig Option) , _icd_perKey :: Map ExactPrint.Types.AnnKey (CConfig Option)
} }
#if MIN_VERSION_ghc(8,2,0) #if MIN_VERSION_ghc(8,2,0)
@ -38,7 +37,7 @@ data InlineConfig = InlineConfig
#endif #endif
type PPM = MultiRWSS.MultiRWS type PPM = MultiRWSS.MultiRWS
'[Map ExactPrint.AnnKey ExactPrint.Anns, InlineConfig, Config, ExactPrint.Anns] '[Map ExactPrint.AnnKey ExactPrint.Anns, PerItemConfig, Config, ExactPrint.Anns]
'[Text.Builder.Builder, [BrittanyError], Seq String] '[Text.Builder.Builder, [BrittanyError], Seq String]
'[] '[]