Change default lexer mode to Opt_KeepRawTokenStream (#2542)

* Change default lexer mode to Opt_KeepRawTokenStream

* Set lexer to Opt_Haddock in daml-doc tests

* Set Opt_Haddock in another daml-doc test
This commit is contained in:
Shayne Fletcher 2019-08-14 14:13:42 -04:00 committed by GitHub
parent d9121af530
commit f85e2430d1
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
8 changed files with 55 additions and 19 deletions

View File

@ -249,7 +249,7 @@ damldocExpect importPathM testname input check =
-- | Generate the docs for a given input file and optional import directory.
runDamldoc :: FilePath -> Maybe FilePath -> IO ModuleDoc
runDamldoc testfile importPathM = do
opts <- defaultOptionsIO Nothing
opts <- fmap (\opt -> opt {optHaddock=Haddock True}) $ defaultOptionsIO Nothing
let opts' = opts
{ optImportPath =

View File

@ -6,6 +6,7 @@ module DA.Daml.Options.Types
, EnableScenarioService(..)
, ScenarioValidation(..)
, DlintUsage(..)
, Haddock(..)
, defaultOptionsIO
, defaultOptions
, mkOptions
@ -64,8 +65,13 @@ data Options = Options
-- ^ Whether we're compiling generated code. Then we allow internal imports.
, optCoreLinting :: Bool
-- ^ Whether to enable linting of the generated GHC Core. (Used in testing.)
, optHaddock :: Haddock
-- ^ Whether to enable lexer option `Opt_Haddock` (default is `Haddock False`).
} deriving Show
newtype Haddock = Haddock Bool
deriving Show
data DlintUsage
= DlintEnabled { dlintUseDataDir :: FilePath, dlintAllowOverrides :: Bool }
| DlintDisabled
@ -145,6 +151,7 @@ defaultOptions mbVersion =
, optDlintUsage = DlintDisabled
, optIsGenerated = False
, optCoreLinting = False
, optHaddock = Haddock False
}
getBaseDir :: IO FilePath

View File

@ -169,8 +169,7 @@ xExtensionsUnset = [ ]
-- | Flags set for DAML-1.2 compilation
xFlagsSet :: Options -> [GeneralFlag]
xFlagsSet options =
[ Opt_Haddock
, Opt_Ticky
[Opt_Ticky
] ++
[ Opt_DoCoreLinting | optCoreLinting options ]
@ -204,8 +203,18 @@ wOptsUnset =
adjustDynFlags :: Options -> DynFlags -> DynFlags
adjustDynFlags options@Options{..} dflags
= setImports optImportPath
$ setThisInstalledUnitId (maybe mainUnitId stringToUnitId optMbPackageName)
=
-- Generally, the lexer's "haddock mode" is disabled (`Haddock
-- False` is the default option. In this case, we run the lexer in
-- "keep raw token stream mode" (meaning basically, harvest all
-- comments encountered during parsing). The exception is when
-- parsing for daml-doc (c.f. `DA.Cli.Damlc.Command.Damldoc`).
(case optHaddock of
Haddock True -> flip gopt_set Opt_Haddock
Haddock False -> flip gopt_set Opt_KeepRawTokenStream
)
$ setImports optImportPath
$ setThisInstalledUnitId (maybe mainUnitId stringToUnitId optMbPackageName)
-- once we have package imports working, we want to import the base package and set this to
-- the default instead of always compiling in the context of ghc-prim.
$ apply wopt_set wOptsSet

View File

@ -843,6 +843,7 @@ optionsParser numProcessors enableScenarioService parsePkgName = Options
<*> dlintUsageOpt
<*> pure False
<*> pure False
<*> pure (Haddock False)
where
optImportPath :: Parser [FilePath]
optImportPath =

View File

@ -193,7 +193,7 @@ data CmdArgs = Damldoc { cInputFormat :: InputFormat
exec :: CmdArgs -> IO ()
exec Damldoc{..} = do
opts <- defaultOptionsIO Nothing
opts <- fmap (\opts -> opts {optHaddock=Haddock True}) $ defaultOptionsIO Nothing
runDamlDoc DamldocOptions
{ do_ideOptions = toCompileOpts opts { optMbPackageName = cPkgName } (IdeReportProgress False)
, do_outputPath = cOutputPath

View File

@ -105,9 +105,8 @@ doctestHeader =
shouldGenerate :: [T.Text] -> [T.Text] -> Assertion
shouldGenerate input expected = withTempFile $ \tmpFile -> do
T.writeFileUtf8 tmpFile $ T.unlines $ testModuleHeader <> input
opts <- defaultOptionsIO Nothing
opts <- fmap (\opts -> opts{optHaddock=Haddock True}) $ defaultOptionsIO Nothing
vfs <- makeVFSHandle
ideState <- initialise mainRule (const $ pure ()) noLogging (toCompileOpts opts (IdeReportProgress False)) vfs
Just pm <- runAction ideState $ use GetParsedModule $ toNormalizedFilePath tmpFile
genModuleContent (getDocTestModule pm) @?= T.unlines (doctestHeader <> expected)

View File

@ -44,6 +44,7 @@ ideTests mbScenarioService =
, minimalRebuildTests mbScenarioService
, goToDefinitionTests mbScenarioService
, onHoverTests mbScenarioService
, dlintSmokeTests mbScenarioService
, scenarioTests mbScenarioService
, visualDamlTests
]
@ -267,6 +268,31 @@ basicTests mbScenarioService = Tasty.testGroup "Basic tests"
testCase' = testCase mbScenarioService
testCaseFails' = testCaseFails mbScenarioService
dlintSmokeTests :: Maybe SS.Handle -> Tasty.TestTree
dlintSmokeTests mbScenarioService = Tasty.testGroup "Dlint smoke tests"
[ testCase' "Suggest imports can be simplified" $ do
foo <- makeFile "Foo.daml" $ T.unlines
[ "daml 1.2"
, "module Foo where"
, "import DA.Optional"
, "import DA.Optional(fromSome)"
]
setFilesOfInterest [foo]
expectNoErrors
expectDiagnostic DsInfo (foo, 2, 0) "Warning: Use fewer imports"
, testCase' "Suggest use fewer pragmas" $ do
foo <- makeFile "Foo.daml" $ T.unlines
[ "{-# LANGUAGE ScopedTypeVariables, RebindableSyntax #-}"
, "{-# LANGUAGE ScopedTypeVariables #-}"
, "daml 1.2"
, "module Foo where"
]
setFilesOfInterest [foo]
expectNoErrors
expectDiagnostic DsInfo (foo, 0, 0) "Warning: Use fewer LANGUAGE pragmas"
]
where
testCase' = testCase mbScenarioService
minimalRebuildTests :: Maybe SS.Handle -> Tasty.TestTree
minimalRebuildTests mbScenarioService = Tasty.testGroup "Minimal rebuild tests"
@ -451,17 +477,6 @@ goToDefinitionTests mbScenarioService = Tasty.testGroup "Go to definition tests"
-- Bool is from GHC.Types which is wired into the compiler
expectGoToDefinition (foo,2,[20]) Missing
, testCase' "Suggest imports can be simplified" $ do
foo <- makeFile "Foo.daml" $ T.unlines
[ "daml 1.2"
, "module Foo where"
, "import DA.Optional"
, "import DA.Optional(fromSome)"
]
setFilesOfInterest [foo]
expectNoErrors
expectDiagnostic DsInfo (foo, 2, 0) "Warning: Use fewer imports"
, testCase' "Go to definition takes export list to definition" $ do
foo <- makeFile "Foo.daml" $ T.unlines
[ "daml 1.2"

View File

@ -83,5 +83,10 @@ docHeaders :: [RealLocated AnnotationComment]
docHeaders = mapMaybe (\(L _ x) -> wrk x)
where
wrk = \case
-- When `Opt_Haddock` is enabled.
AnnDocCommentNext s -> Just $ T.pack s
-- When `Opt_KeepRawTokenStream` enabled.
AnnLineComment s -> if "-- |" `isPrefixOf` s
then Just $ T.pack s
else Nothing
_ -> Nothing