Deprecate the "daml 1.2" version header. (#7513)

* changelog_begin

- [DAML] The "daml 1.2" version header is now deprecated.

changelog_end

* fix some line numbers

* fix some more locations
This commit is contained in:
Sofia Faro 2020-09-29 14:14:59 +01:00 committed by GitHub
parent 168345f4a8
commit e9cd92f061
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
22 changed files with 351 additions and 479 deletions

View File

@ -284,8 +284,7 @@ writeMinimalProject (SdkVersion sdkVersion) = do
, " - daml-stdlib"
]
writeFileUTF8 "Main.daml" $ unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "template T with p : Party where signatory p"
]

View File

@ -139,7 +139,6 @@ renderDocTestModule DocTestModule{..} = rendered
testsWithIds = zip [DocTestId 0..] dtModuleContent
rendered = T.unlines $
[ "{-# OPTIONS_GHC -Wno-unused-imports #-}"
, "daml 1.2"
, "module " <> docTestModuleName dtModuleName <> " where"
, ""
, "import " <> dtModuleName
@ -170,4 +169,3 @@ data GeneratedModule = GeneratedModule
} deriving (Show, Generic)
instance NFData GeneratedModule

View File

@ -216,8 +216,7 @@ makeModule :: String -> [T.Text] -> ShakeTest D.NormalizedFilePath
makeModule modName body = do
let modPath = moduleNameToFilePath modName
makeFile modPath . T.unlines $
[ "daml 1.2"
, "module " <> T.pack modName <> " where"
[ "module " <> T.pack modName <> " where"
] ++ body
-- | Set files of interest.
@ -534,8 +533,7 @@ expectedGraph damlFilePath expectedGraph = do
example :: ShakeTest ()
example = do
fooPath <- makeFile "src/Foo.daml" $ T.unlines
[ "daml 1.2"
, "module Foo where"
[ "module Foo where"
, "data Foo = Foo"
, " with"
, " bar : Party"

View File

@ -63,7 +63,7 @@ damlPreprocessor :: Maybe GHC.UnitId -> GHC.ParsedSource -> IdePreprocessedSourc
damlPreprocessor mbUnitId x
| maybe False (isInternal ||^ (`elem` mayImportInternal)) name = noPreprocessor x
| otherwise = IdePreprocessedSource
{ preprocWarnings = checkVariantUnitConstructors x
{ preprocWarnings = checkDamlHeader x ++ checkVariantUnitConstructors x
, preprocErrors = checkImports x ++ checkDataTypes x ++ checkModuleDefinition x ++ checkRecordConstructor x ++ checkModuleName x
, preprocSource = recordDotPreprocessor $ importDamlPreprocessor $ genericsPreprocessor mbUnitId $ enumTypePreprocessor "GHC.Types" x
}
@ -120,6 +120,16 @@ checkImports x =
[ (ss, "Import of internal module " ++ GHC.moduleNameString m ++ " is not allowed.")
| GHC.L ss GHC.ImportDecl{ideclName=GHC.L _ m} <- GHC.hsmodImports $ GHC.unLoc x, isInternal m]
-- | Emit a warning if the "daml 1.2" version header is present.
checkDamlHeader :: GHC.ParsedSource -> [(GHC.SrcSpan, String)]
checkDamlHeader (GHC.L _ m)
| Just (GHC.L ss doc) <- GHC.hsmodHaddockModHeader m
, "HAS_DAML_VERSION_HEADER" `isPrefixOf` GHC.unpackHDS doc
= [(ss, "The \"daml 1.2\" version header is deprecated, please remove it.")]
| otherwise
= []
-- | Emit a warning if a variant constructor has a single argument of unit type '()'.
-- See issue #7207.
checkVariantUnitConstructors :: GHC.ParsedSource -> [(GHC.SrcSpan, String)]

View File

@ -1,4 +1,5 @@
daml 1.2
-- @WARN The "daml 1.2" version header is deprecated, please remove it.
-- | Testing the daml version header.
module DamlHasVersion(T, main) where

View File

@ -86,14 +86,12 @@ generateTests = testGroup "generate doctest module"
testModuleHeader :: [T.Text]
testModuleHeader =
[ "daml 1.2"
, "module Test where"
[ "module Test where"
]
doctestHeader :: [T.Text]
doctestHeader =
[ "{-# OPTIONS_GHC -Wno-unused-imports #-}"
, "daml 1.2"
, "module Test_doctest where"
, ""
, "import Test"

View File

@ -23,8 +23,7 @@ tests damlcPath = testGroup "doctest integration tests"
withTempDir $ \tmpDir -> do
let f = tmpDir </> "Main.daml"
writeFileUTF8 f $ unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "-- | add"
, "-- >>> add 1 1"
, "-- 2"
@ -43,8 +42,7 @@ tests damlcPath = testGroup "doctest integration tests"
withTempDir $ \tmpDir -> do
let f = tmpDir </> "Main.daml"
writeFileUTF8 f $ unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "-- | add"
, "-- >>> add 1 1"
, "-- 2"

View File

@ -32,7 +32,7 @@ mkModule n = T.unlines
]
mkHeader :: Int -> T.Text
mkHeader n = T.pack $ "daml 1.2\nmodule " <> stdModName n <> "\n where"
mkHeader n = T.pack $ "module " <> stdModName n <> "\n where"
mkImport :: Int -> T.Text
mkImport k = T.pack $ "import qualified " <> stdModName k

View File

@ -25,8 +25,7 @@ tests :: FilePath -> FilePath -> TestTree
tests damlc repl = testGroup "Incremental builds"
[ test "No changes"
[ ("daml/A.daml", unlines
[ "daml 1.2"
, "module A where"
[ "module A where"
]
)
]
@ -35,15 +34,13 @@ tests damlc repl = testGroup "Incremental builds"
(ShouldSucceed True)
, test "Modify single file"
[ ("daml/A.daml", unlines
[ "daml 1.2"
, "module A where"
[ "module A where"
, "test = scenario $ assert True"
]
)
]
[ ("daml/A.daml", unlines
[ "daml 1.2"
, "module A where"
[ "module A where"
, "test = scenario $ assert False"
]
)
@ -52,22 +49,19 @@ tests damlc repl = testGroup "Incremental builds"
(ShouldSucceed False)
, test "Modify dependency without ABI change"
[ ("daml/A.daml", unlines
[ "daml 1.2"
, "module A where"
[ "module A where"
, "import B"
, "test = scenario $ b"
]
)
, ("daml/B.daml", unlines
[ "daml 1.2"
, "module B where"
[ "module B where"
, "b = scenario $ assert True"
]
)
]
[ ("daml/B.daml", unlines
[ "daml 1.2"
, "module B where"
[ "module B where"
, "b = scenario $ assert False"
]
)
@ -76,23 +70,20 @@ tests damlc repl = testGroup "Incremental builds"
(ShouldSucceed False)
, test "Modify dependency with ABI change"
[ ("daml/A.daml", unlines
[ "daml 1.2"
, "module A where"
[ "module A where"
, "import B"
, "test = scenario $ do _ <- b; pure ()"
]
)
, ("daml/B.daml", unlines
[ "daml 1.2"
, "module B where"
[ "module B where"
, "b : Scenario Bool"
, "b = pure True"
]
)
]
[ ("daml/B.daml", unlines
[ "daml 1.2"
, "module B where"
[ "module B where"
, "b : Scenario ()"
, "b = assert False"
]
@ -104,7 +95,7 @@ tests damlc repl = testGroup "Incremental builds"
-- This test checks that we setup dependent modules in the right order. Note that just having imports is not sufficient
-- to trigger this. The modules actually need to use identifiers from the other modules.
[ ("daml/A.daml", unlines
[ "daml 1.2 module A where"
[ "module A where"
, "import B"
, "test = scenario $ do"
, " p <- getParty \"Alice\""
@ -113,7 +104,7 @@ tests damlc repl = testGroup "Incremental builds"
]
)
, ("daml/B.daml", unlines
[ "daml 1.2 module B (module C, Y(..)) where"
[ "module B (module C, Y(..)) where"
, "import C"
, "template Y"
, " with p : Party; cid : ContractId X"
@ -121,7 +112,7 @@ tests damlc repl = testGroup "Incremental builds"
]
)
, ("daml/C.daml", unlines
[ "daml 1.2 module C where"
[ "module C where"
, "template X"
, " with p : Party"
, " where signatory p"

View File

@ -416,7 +416,7 @@ tests tools@Tools{damlc} = testGroup "Packaging" $
, "dependencies: [daml-prim, daml-stdlib]"
]
writeFileUTF8 (projDir </> "A.daml") $ unlines
[ "daml 1.2 module A where"
[ "module A where"
]
withCurrentDirectory projDir $ callProcessSilent damlc ["build", "-o", "foobar.dar", "--target=1.dev"]
Right Dalfs{..} <- readDalfs . Zip.toArchive <$> BSL.readFile (projDir </> "foobar.dar")
@ -627,7 +627,7 @@ tests tools@Tools{damlc} = testGroup "Packaging" $
, "build-options: [--target=1.8]"
]
writeFileUTF8 (tmpDir </> "a" </> "A.daml") $ unlines
[ "daml 1.2 module A where"
[ "module A where"
]
withCurrentDirectory (tmpDir </> "a") $ callProcessSilent damlc ["build", "-o", tmpDir </> "a" </> "a.dar"]
@ -646,7 +646,7 @@ tests tools@Tools{damlc} = testGroup "Packaging" $
, "build-options: [--target=1.7]"
]
writeFileUTF8 (tmpDir </> "b" </> "B.daml") $ unlines
[ "daml 1.2 module B where"
[ "module B where"
, "import A ()"
]
buildProjectError (tmpDir </> "b") "" "Targeted LF version 1.7 but dependencies have newer LF versions"
@ -663,7 +663,7 @@ tests tools@Tools{damlc} = testGroup "Packaging" $
, "build-options: [--target=1.8]"
]
writeFileUTF8 (tmpDir </> "a" </> "A.daml") $ unlines
[ "daml 1.2 module A where"
[ "module A where"
]
withCurrentDirectory (tmpDir </> "a") $ callProcessSilent damlc ["build", "-o", tmpDir </> "a" </> "a.dar"]
@ -681,7 +681,7 @@ tests tools@Tools{damlc} = testGroup "Packaging" $
, "build-options: [--target=1.7]"
]
writeFileUTF8 (tmpDir </> "b" </> "B.daml") $ unlines
[ "daml 1.2 module B where"
[ "module B where"
, "import A ()"
]
buildProjectError (tmpDir </> "b") "" "Targeted LF version 1.7 but dependencies have newer LF versions"
@ -854,7 +854,7 @@ lfVersionTests damlc = testGroup "LF version dependencies"
, "dependencies: [daml-prim, daml-stdlib]"
]
writeFileUTF8 (projDir </> "A.daml") $ unlines
[ "daml 1.2 module A where"]
[ "module A where"]
withCurrentDirectory projDir $ callProcessSilent damlc ["build", "-o", projDir </> "proj.dar", "--target", LF.renderVersion version]
archive <- Zip.toArchive <$> BSL.readFile (projDir </> "proj.dar")
DalfManifest {mainDalfPath, dalfPaths} <- either fail pure $ readDalfManifest archive
@ -891,8 +891,7 @@ dataDependencyTests Tools{damlc,repl,validate,davlDar,oldProjDar} = testGroup "D
step "Build proja"
createDirectoryIfMissing True (proja </> "src")
writeFileUTF8 (proja </> "src" </> "A.daml") $ unlines
[" daml 1.2"
, "module A where"
[ "module A where"
, "import DA.Text"
, "data A = A Int deriving Show"
-- This ensures that we have a reference to daml-stdlib and therefore daml-prim.
@ -1022,7 +1021,7 @@ dataDependencyTests Tools{damlc,repl,validate,davlDar,oldProjDar} = testGroup "D
, "dependencies: [daml-prim, daml-stdlib]"
]
writeFileUTF8 (tmpDir </> "lib" </> "Lib.daml") $ unlines
[ "daml 1.2 module Lib where"
[ "module Lib where"
, "inc : Int -> Int"
, "inc = (+ 1)"
]
@ -1042,7 +1041,7 @@ dataDependencyTests Tools{damlc,repl,validate,davlDar,oldProjDar} = testGroup "D
, " - " <> show (tmpDir </> "lib" </> "lib.dar")
]
writeFileUTF8 (tmpDir </> "a" </> "A.daml") $ unlines
[ "daml 1.2 module A where"
[ "module A where"
, "import Lib"
, "two : Int"
, "two = inc 1"
@ -1065,7 +1064,7 @@ dataDependencyTests Tools{damlc,repl,validate,davlDar,oldProjDar} = testGroup "D
, "data-dependencies: [" <> show (tmpDir </> "a" </> "a.dar") <> "]"
]
writeFileUTF8 (tmpDir </> "b" </> "B.daml") $ unlines
[ "daml 1.2 module B where"
[ "module B where"
, "import Lib"
, "import A"
, "three : Int"
@ -1215,7 +1214,7 @@ dataDependencyTests Tools{damlc,repl,validate,davlDar,oldProjDar} = testGroup "D
, "dependencies: [daml-prim, daml-stdlib]"
]
writeFileUTF8 (projDir </> "Lib.daml") $ unlines
[ "daml 1.2 module Lib where"
[ "module Lib where"
, "data X" <> version <> " = X"
]
withCurrentDirectory projDir $ callProcessSilent damlc ["build", "-o", projDir </> "lib.dar"]
@ -1233,7 +1232,7 @@ dataDependencyTests Tools{damlc,repl,validate,davlDar,oldProjDar} = testGroup "D
, "- " <> show (tmpDir </> "lib-1" </> "lib.dar")
]
writeFileUTF8 (projDir </> "A.daml") $ unlines
[ "daml 1.2 module A where"
[ "module A where"
, "import Lib"
, "data A = A X1"
]
@ -1253,7 +1252,7 @@ dataDependencyTests Tools{damlc,repl,validate,davlDar,oldProjDar} = testGroup "D
, "- " <> show (tmpDir </> "a" </> "a.dar")
]
writeFileUTF8 (projDir </> "B.daml") $ unlines
[ "daml 1.2 module B where"
[ "module B where"
, "import Lib"
, "import A"
, "data B1 = B1 A"
@ -1278,7 +1277,7 @@ dataDependencyTests Tools{damlc,repl,validate,davlDar,oldProjDar} = testGroup "D
, "- " <> show (tmpDir </> "lib-2" </> "lib.dar")
]
writeFileUTF8 (projDir </> "C.daml") $ unlines
[ "daml 1.2 module C where"
[ "module C where"
, "import B"
, "import Lib"
, "f : B2 -> X2"
@ -1560,7 +1559,7 @@ dataDependencyTests Tools{damlc,repl,validate,davlDar,oldProjDar} = testGroup "D
, "build-options: [--target=1.dev]"
]
writeFileUTF8 (tmpDir </> "type" </> "Proxy.daml") $ unlines
[ "daml 1.2 module Proxy where"
[ "module Proxy where"
, "data Proxy a = Proxy {}"
]
withCurrentDirectory (tmpDir </> "type") $ callProcessSilent damlc ["build", "-o", "type.dar"]
@ -1577,7 +1576,7 @@ dataDependencyTests Tools{damlc,repl,validate,davlDar,oldProjDar} = testGroup "D
, "build-options: [ \"--target=1.dev\" ]"
]
writeFileUTF8 (tmpDir </> "dependency" </> "Dependency.daml") $ unlines
[ "daml 1.2 module Dependency where"
[ "module Dependency where"
, "import Proxy"
, "instance Functor Proxy where"
, " fmap _ Proxy = Proxy"
@ -1596,7 +1595,7 @@ dataDependencyTests Tools{damlc,repl,validate,davlDar,oldProjDar} = testGroup "D
, "build-options: [ \"--target=1.dev\" ]"
]
writeFileUTF8 (tmpDir </> "data-dependency" </> "DataDependency.daml") $ unlines
[ "daml 1.2 module DataDependency where"
[ "module DataDependency where"
, "import Proxy"
, "instance Functor Proxy where"
, " fmap _ Proxy = Proxy"
@ -1618,7 +1617,7 @@ dataDependencyTests Tools{damlc,repl,validate,davlDar,oldProjDar} = testGroup "D
, "build-options: [--target=1.dev]"
]
writeFileUTF8 (tmpDir </> "top" </> "Top.daml") $ unlines
[ "daml 1.2 module Top where"
[ "module Top where"
, "import DataDependency"
, "import Proxy"
-- Test that we can use the Applicaive instance of Proxy from the data-dependency

File diff suppressed because it is too large Load Diff

View File

@ -53,7 +53,7 @@ testsForDamlcValidate damlc = testGroup "damlc validate-dar"
, "dependencies: [daml-prim, daml-stdlib]"
]
writeFileUTF8 (projDir </> "Good.daml") $ unlines
[ "daml 1.2 module Good where"
[ "module Good where"
, "good = 1 + 2"
]
step "build"
@ -75,7 +75,7 @@ testsForDamlcValidate damlc = testGroup "damlc validate-dar"
, "dependencies: [daml-prim, daml-stdlib]"
]
writeFileUTF8 (projDir </> "Good.daml") $ unlines
[ "daml 1.2 module Good where"
[ "module Good where"
, "template MyT"
, " with"
, " myParty : Party"
@ -101,7 +101,7 @@ testsForDamlcValidate damlc = testGroup "damlc validate-dar"
, "dependencies: [daml-prim, daml-stdlib]"
]
writeFileUTF8 (projDir </> "Good.daml") $ unlines
[ "daml 1.2 module Good where"
[ "module Good where"
, "good = 1"
]
step "build"
@ -131,7 +131,7 @@ testsForDamlcValidate damlc = testGroup "damlc validate-dar"
, "dependencies: [daml-prim, daml-stdlib]"
]
writeFileUTF8 (projDir </> "Good.daml") $ unlines
[ "daml 1.2 module Good where"
[ "module Good where"
, "good = 1"
]
step "build"
@ -163,8 +163,7 @@ testsForDamlcTest damlc = testGroup "damlc test" $
withTempDir $ \dir -> do
let file = dir </> "Foo.daml"
T.writeFileUtf8 file $ T.unlines
[ "daml 1.2"
, "module Foo where"
[ "module Foo where"
, "abc"
]
(exitCode, stdout, stderr) <- readProcessWithExitCode damlc ["test", "--files", file] ""
@ -175,8 +174,7 @@ testsForDamlcTest damlc = testGroup "damlc test" $
withTempDir $ \dir -> do
let file = dir </> "Foo.daml"
T.writeFileUtf8 file $ T.unlines
[ "daml 1.2"
, "module Foo where"
[ "module Foo where"
, "x = scenario $ assert False"
]
(exitCode, stdout, stderr) <- readProcessWithExitCode damlc ["test", "--files", file] ""
@ -185,8 +183,7 @@ testsForDamlcTest damlc = testGroup "damlc test" $
exitCode @?= ExitFailure 1
, testCase "damlc test --files outside of project" $ withTempDir $ \projDir -> do
writeFileUTF8 (projDir </> "Main.daml") $ unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "test = scenario do"
, " assert True"
]
@ -197,8 +194,7 @@ testsForDamlcTest damlc = testGroup "damlc test" $
, testCase "damlc test --project-root relative" $ withTempDir $ \projDir -> do
createDirectoryIfMissing True (projDir </> "relative")
writeFileUTF8 (projDir </> "relative" </> "Main.daml") $ unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "test = scenario do"
, " assert True"
]
@ -222,7 +218,7 @@ testsForDamlcTest damlc = testGroup "damlc test" $
, "dependencies: [daml-prim, daml-stdlib]"
]
writeFileUTF8 (projDir </> "a" </> "A.daml") $ unlines
[ "daml 1.2 module A where"
[ "module A where"
, "a = 1"
]
callProcessSilent damlc ["build", "--project-root", projDir </> "a"]
@ -235,7 +231,7 @@ testsForDamlcTest damlc = testGroup "damlc test" $
, "dependencies: [daml-prim, daml-stdlib, " <> show (projDir </> "a/.daml/dist/a-0.0.1.dar") <> "]"
]
writeFileUTF8 (projDir </> "b" </> "B.daml") $ unlines
[ "daml 1.2 module B where"
[ "module B where"
, "import A"
, "b = a"
, "test = scenario do"

View File

@ -76,7 +76,6 @@ dependencies: [daml-prim, daml-stdlib]
EOF
cat <<EOF > "$PROJDIR/A.daml"
daml 1.2
module A where
EOF

View File

@ -78,27 +78,23 @@ diagnosticTests
diagnosticTests run runScenarios = testGroup "diagnostics"
[ testCase "diagnostics disappear after error is fixed" $ run $ do
test <- openDoc' "Test.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Test where"
[ "module Test where"
, "f 1"
]
expectDiagnostics [("Test.daml", [(DsError, (2, 0), "Parse error")])]
expectDiagnostics [("Test.daml", [(DsError, (1, 0), "Parse error")])]
replaceDoc test $ T.unlines
[ "daml 1.2"
, "module Test where"
[ "module Test where"
, "f = ()"
]
expectDiagnostics [("Test.daml", [])]
closeDoc test
, testCase "lower-case drive" $ run $ do
let aContent = T.unlines
[ "daml 1.2"
, "module A.A where"
[ "module A.A where"
, "import A.B ()"
]
bContent = T.unlines
[ "daml 1.2"
, "module A.B where"
[ "module A.B where"
, "import DA.List"
]
uriB <- getDocUri "A/B.daml"
@ -127,38 +123,33 @@ diagnosticTests run runScenarios = testGroup "diagnostics"
closeDoc a
, testCase "diagnostics appear after introducing an error" $ run $ do
test <- openDoc' "Test.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Test where"
[ "module Test where"
, "f = ()"
]
replaceDoc test $ T.unlines
[ "daml 1.2"
, "module Test where"
[ "module Test where"
, "f 1"
]
expectDiagnostics [("Test.daml", [(DsError, (2, 0), "Parse error")])]
expectDiagnostics [("Test.daml", [(DsError, (1, 0), "Parse error")])]
closeDoc test
, testCase "percent encoding does not matter" $ run $ do
Just uri <- parseURI . T.unpack . getUri <$> getDocUri "Test.daml"
let weirdUri = Uri $ T.pack $ "file://" <> escapeURIString (== '/') (uriPath uri)
let item = TextDocumentItem weirdUri (T.pack damlId) 0 $ T.unlines
[ "daml 1.2"
, "module Test where"
[ "module Test where"
, "f = ()"
]
sendNotification TextDocumentDidOpen (DidOpenTextDocumentParams item)
let test = TextDocumentIdentifier weirdUri
replaceDoc test $ T.unlines
[ "daml 1.2"
, "module Test where"
[ "module Test where"
, "f 1"
]
expectDiagnostics [("Test.daml", [(DsError, (2, 0), "Parse error")])]
expectDiagnostics [("Test.daml", [(DsError, (1, 0), "Parse error")])]
closeDoc test
, testCase "failed name resolution" $ run $ do
main' <- openDoc' "Main.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "add : Int -> Int -> Int"
, "add a b = ab + b"
, "succ : Int -> Int"
@ -166,64 +157,58 @@ diagnosticTests run runScenarios = testGroup "diagnostics"
]
expectDiagnostics
[ ( "Main.daml"
, [ (DsError, (3, 10), "Variable not in scope: ab")
, (DsError, (5, 7), "Variable not in scope: abdd")
, [ (DsError, (2, 10), "Variable not in scope: ab")
, (DsError, (4, 7), "Variable not in scope: abdd")
]
)
]
closeDoc main'
, testCase "import cycle" $ run $ do
let aContent = T.unlines
[ "daml 1.2"
, "module A where"
[ "module A where"
, "import B"
]
bContent = T.unlines
[ "daml 1.2"
, "module B where"
[ "module B where"
, "import A"
]
[a, b] <- openDocs damlId [("A.daml", aContent), ("B.daml", bContent)]
expectDiagnostics
[ ( "A.daml"
, [(DsError, (2, 7), "Cyclic module dependency between A, B")]
, [(DsError, (1, 7), "Cyclic module dependency between A, B")]
)
, ( "B.daml"
, [(DsError, (2, 7), "Cyclic module dependency between A, B")]
, [(DsError, (1, 7), "Cyclic module dependency between A, B")]
)
]
closeDoc b
closeDoc a
, testCase "import error" $ run $ do
main' <- openDoc' "Main.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "import Oops"
]
expectDiagnostics
[("Main.daml", [(DsError, (2, 7), "Could not find module 'Oops'")])]
[("Main.daml", [(DsError, (1, 7), "Could not find module 'Oops'")])]
closeDoc main'
, testCase "multi module funny" $ run $ do
libsC <- openDoc' "Libs/C.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Libs.C where"
[ "module Libs.C where"
]
libsB <- openDoc' "Libs/B.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Libs.B where"
[ "module Libs.B where"
, "import Libs.C"
]
libsA <- openDoc' "Libs/A.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Libs.A where"
[ "module Libs.A where"
, "import C"
]
expectDiagnostics
[ ( "Libs/A.daml"
, [(DsError, (2, 7), "Could not find module 'C'")]
, [(DsError, (1, 7), "Could not find module 'C'")]
)
, ( "Libs/B.daml"
, [(DsWarning, (2, 0), "import of 'Libs.C' is redundant")]
, [(DsWarning, (1, 0), "import of 'Libs.C' is redundant")]
)
]
closeDoc libsA
@ -231,22 +216,20 @@ diagnosticTests run runScenarios = testGroup "diagnostics"
closeDoc libsC
, testCase "parse error" $ run $ do
test <- openDoc' "Test.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Test where"
[ "module Test where"
, "f 1"
]
expectDiagnostics [("Test.daml", [(DsError, (2, 0), "Parse error")])]
expectDiagnostics [("Test.daml", [(DsError, (1, 0), "Parse error")])]
closeDoc test
, testCase "type error" $ run $ do
main' <- openDoc' "Main.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "oops = 1 + \"foo\""
]
expectDiagnostics
[ ( "Main.daml"
, [ ( DsError
, (2, 11)
, (1, 11)
, "Couldn't match expected type 'Int' with actual type 'Text'"
)
]
@ -255,8 +238,7 @@ diagnosticTests run runScenarios = testGroup "diagnostics"
closeDoc main'
, testCase "scenario error" $ runScenarios $ do
main' <- openDoc' "Main.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "template Agree with p1 : Party; p2 : Party where"
, " signatory [p1, p2]"
, "myScenario = scenario do"
@ -266,7 +248,7 @@ diagnosticTests run runScenarios = testGroup "diagnostics"
]
expectDiagnostics
[ ( "Main.daml"
, [(DsError, (4, 0), "missing authorization from 'Alice'")]
, [(DsError, (3, 0), "missing authorization from 'Alice'")]
)
]
closeDoc main'
@ -280,8 +262,7 @@ requestTests
requestTests run _runScenarios = testGroup "requests"
[ testCase "code-lenses" $ run $ do
main' <- openDoc' "Main.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "single = scenario do"
, " assert (True == True)"
]
@ -289,7 +270,7 @@ requestTests run _runScenarios = testGroup "requests"
Just escapedFp <- pure $ escapeURIString isUnescapedInURIComponent <$> uriToFilePath (main' ^. uri)
liftIO $ lenses @?=
[ CodeLens
{ _range = Range (Position 2 0) (Position 2 6)
{ _range = Range (Position 1 0) (Position 1 6)
, _command = Just $ Command
{ _title = "Scenario results"
, _command = "daml.showResource"
@ -305,8 +286,7 @@ requestTests run _runScenarios = testGroup "requests"
closeDoc main'
, testCase "stale code-lenses" $ run $ do
main' <- openDoc' "Main.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "single = scenario do"
, " assert True"
]
@ -325,20 +305,19 @@ requestTests run _runScenarios = testGroup "requests"
}
, _xdata = Nothing
}
liftIO $ lenses @?= [codeLens (Range (Position 2 0) (Position 2 6))]
changeDoc main' [TextDocumentContentChangeEvent (Just (Range (Position 3 23) (Position 3 23))) Nothing "+"]
expectDiagnostics [("Main.daml", [(DsError, (4, 0), "Parse error")])]
liftIO $ lenses @?= [codeLens (Range (Position 1 0) (Position 1 6))]
changeDoc main' [TextDocumentContentChangeEvent (Just (Range (Position 2 23) (Position 2 23))) Nothing "+"]
expectDiagnostics [("Main.daml", [(DsError, (3, 0), "Parse error")])]
lenses <- getCodeLenses main'
liftIO $ lenses @?= [codeLens (Range (Position 2 0) (Position 2 6))]
liftIO $ lenses @?= [codeLens (Range (Position 1 0) (Position 1 6))]
-- Shift code lenses down
changeDoc main' [TextDocumentContentChangeEvent (Just (Range (Position 1 0) (Position 1 0))) Nothing "\n\n"]
changeDoc main' [TextDocumentContentChangeEvent (Just (Range (Position 0 0) (Position 0 0))) Nothing "\n\n"]
lenses <- getCodeLenses main'
liftIO $ lenses @?= [codeLens (Range (Position 4 0) (Position 4 6))]
liftIO $ lenses @?= [codeLens (Range (Position 3 0) (Position 3 6))]
closeDoc main'
, testCase "type on hover: name" $ run $ do
main' <- openDoc' "Main.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "add : Int -> Int -> Int"
, "add a b = a + b"
, "template DoStuff with party : Party where"
@ -349,7 +328,7 @@ requestTests run _runScenarios = testGroup "requests"
, " do pure (add 5 number)"
]
Just fp <- pure $ uriToFilePath (main' ^. uri)
r <- getHover main' (Position 9 19)
r <- getHover main' (Position 8 19)
liftIO $ r @?= Just Hover
{ _contents = HoverContents $ MarkupContent MkMarkdown $ T.unlines
[ "```daml"
@ -357,19 +336,18 @@ requestTests run _runScenarios = testGroup "requests"
, ": Int -> Int -> Int"
, "```"
, "*\t*\t*"
, "*Defined at " <> T.pack fp <> ":4:1*"
, "*Defined at " <> T.pack fp <> ":3:1*"
]
, _range = Just $ Range (Position 9 17) (Position 9 20)
, _range = Just $ Range (Position 8 17) (Position 8 20)
}
closeDoc main'
, testCase "type on hover: literal" $ run $ do
main' <- openDoc' "Main.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "simple arg1 = let xlocal = 1.0 in xlocal + arg1"
]
r <- getHover main' (Position 2 27)
r <- getHover main' (Position 1 27)
liftIO $ r @?= Just Hover
{ _contents = HoverContents $ MarkupContent MkMarkdown $ T.unlines
[ "```daml"
@ -379,18 +357,16 @@ requestTests run _runScenarios = testGroup "requests"
, "```"
, "*\t*\t*"
]
, _range = Just $ Range (Position 2 27) (Position 2 30)
, _range = Just $ Range (Position 1 27) (Position 1 30)
}
closeDoc main'
, testCase "definition" $ run $ do
test <- openDoc' "Test.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Test where"
[ "module Test where"
, "answerFromTest = 42"
]
main' <- openDoc' "Main.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "import Test"
, "bar = answerFromTest"
, "foo thisIsAParam = thisIsAParam <> \" concatenated with a Text.\""
@ -407,20 +383,20 @@ requestTests run _runScenarios = testGroup "requests"
, " pure ()"
]
-- thisIsAParam
locs <- getDefinitions main' (Position 4 24)
liftIO $ locs @?= [Location (main' ^. uri) (Range (Position 4 4) (Position 4 16))]
locs <- getDefinitions main' (Position 3 24)
liftIO $ locs @?= [Location (main' ^. uri) (Range (Position 3 4) (Position 3 16))]
-- letParam
locs <- getDefinitions main' (Position 5 37)
liftIO $ locs @?= [Location (main' ^. uri) (Range (Position 5 16) (Position 5 24))]
locs <- getDefinitions main' (Position 4 37)
liftIO $ locs @?= [Location (main' ^. uri) (Range (Position 4 16) (Position 4 24))]
-- import Test
locs <- getDefinitions main' (Position 2 10)
locs <- getDefinitions main' (Position 1 10)
liftIO $ locs @?= [Location (test ^. uri) (Range (Position 0 0) (Position 0 0))]
-- use of `bar` in template
locs <- getDefinitions main' (Position 14 20)
liftIO $ locs @?= [Location (main' ^. uri) (Range (Position 3 0) (Position 3 3))]
locs <- getDefinitions main' (Position 13 20)
liftIO $ locs @?= [Location (main' ^. uri) (Range (Position 2 0) (Position 2 3))]
-- answerFromTest
locs <- getDefinitions main' (Position 3 8)
liftIO $ locs @?= [Location (test ^. uri) (Range (Position 2 0) (Position 2 14))]
locs <- getDefinitions main' (Position 2 8)
liftIO $ locs @?= [Location (test ^. uri) (Range (Position 1 0) (Position 1 14))]
closeDoc main'
closeDoc test
]
@ -429,15 +405,14 @@ scenarioTests :: (Session () -> IO ()) -> TestTree
scenarioTests run = testGroup "scenarios"
[ testCase "opening codelens produces a notification" $ run $ do
main' <- openDoc' "Main.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "main = scenario $ assert (True == True)"
]
lenses <- getCodeLenses main'
uri <- scenarioUri "Main.daml" "main"
liftIO $ lenses @?=
[ CodeLens
{ _range = Range (Position 2 0) (Position 2 4)
{ _range = Range (Position 1 0) (Position 1 4)
, _command = Just $ Command
{ _title = "Scenario results"
, _command = "daml.showResource"
@ -454,8 +429,7 @@ scenarioTests run = testGroup "scenarios"
closeDoc mainScenario
, testCase "scenario ok" $ run $ do
main' <- openDoc' "Main.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "main = scenario $ pure \"ok\""
]
scenario <- openScenario "Main.daml" "main"
@ -464,8 +438,7 @@ scenarioTests run = testGroup "scenarios"
closeDoc main'
, testCase "spaces in path" $ run $ do
main' <- openDoc' "spaces in path/Main.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "main = scenario $ pure \"ok\""
]
scenario <- openScenario "spaces in path/Main.daml" "main"
@ -580,8 +553,7 @@ executeCommandTests :: (forall a. Session a -> IO a) -> (Session () -> IO ()) ->
executeCommandTests run _ = testGroup "execute command"
[ testCase "execute commands" $ run $ do
main' <- openDoc' "Coin.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Coin where"
[ "module Coin where"
, "template Coin"
, " with"
, " owner : Party"
@ -599,8 +571,7 @@ executeCommandTests run _ = testGroup "execute command"
closeDoc main'
, testCase "Invalid commands result in error" $ run $ do
main' <- openDoc' "Empty.daml" damlId $ T.unlines
[ "daml 1.2"
, "module Empty where"
[ "module Empty where"
]
Just escapedFp <- pure $ uriToFilePath (main' ^. uri)
actualDotString :: ExecuteCommandResponse <- LSP.request WorkspaceExecuteCommand $ ExecuteCommandParams
@ -629,8 +600,7 @@ stressTests run _runScenarios = testGroup "Stress tests"
fooValue i = T.pack (show (i `div` 2))
<> if even i then "" else ".5"
fooContent i = T.unlines
[ "daml 1.2"
, "module Foo where"
[ "module Foo where"
, "foo : Int"
, "foo = " <> fooValue i
]
@ -664,7 +634,7 @@ stressTests run _runScenarios = testGroup "Stress tests"
foos <- forM [1 .. 10 :: Int] $ \i ->
makeModule ("Foo" ++ show i) ["foo 10"]
expectDiagnostics
[ ("Foo" ++ show i ++ ".daml", [(DsError, (2, 0), "Parse error")])
[ ("Foo" ++ show i ++ ".daml", [(DsError, (1, 0), "Parse error")])
| i <- [1 .. 10 :: Int]
]
forM_ (zip [1 .. 10 :: Int] foos) $ \(i, foo) ->
@ -695,7 +665,7 @@ stressTests run _runScenarios = testGroup "Stress tests"
, "foo0 = foo1"
]
withTimeout 90 $ do
expectDiagnostics [("Foo0.daml", [(DsError, (4, 7), "Couldn't match expected type")])]
expectDiagnostics [("Foo0.daml", [(DsError, (3, 7), "Couldn't match expected type")])]
void $ replaceDoc foo0 $ moduleContent "Foo0"
[ "import Foo1"
, "foo0 : Bool"
@ -707,8 +677,7 @@ stressTests run _runScenarios = testGroup "Stress tests"
where
moduleContent :: String -> [T.Text] -> T.Text
moduleContent name lines = T.unlines $
[ "daml 1.2"
, "module " <> T.pack name <> " where"
[ "module " <> T.pack name <> " where"
] ++ lines
makeModule :: String -> [T.Text] -> Session TextDocumentIdentifier
makeModule name lines = openDoc' (name ++ ".daml") damlId $
@ -724,20 +693,19 @@ regressionTests run _runScenarios = testGroup "regression"
-- since we used a function from GHCi in ghcide.
foo <- openDoc' "Foo.daml" damlId $ T.unlines
[ "{-# OPTIONS_GHC -Wall #-}"
, "daml 1.2"
, "module Foo where"
, "import DA.List"
, ""
]
expectDiagnostics [("Foo.daml", [(DsWarning, (3,0), "redundant")])]
completions <- getCompletions foo (Position 3 1)
expectDiagnostics [("Foo.daml", [(DsWarning, (2,0), "redundant")])]
completions <- getCompletions foo (Position 2 1)
liftIO $
assertBool ("DA.List and DA.Internal.RebindableSyntax should be in " <> show completions) $
mkModuleCompletion "DA.Internal.RebindableSyntax" `elem` completions &&
mkModuleCompletion "DA.List" `elem` completions
changeDoc foo [TextDocumentContentChangeEvent (Just (Range (Position 3 0) (Position 3 1))) Nothing "Syntax"]
expectDiagnostics [("Foo.daml", [(DsError, (3,0), "Parse error")])]
completions <- getCompletions foo (Position 3 6)
changeDoc foo [TextDocumentContentChangeEvent (Just (Range (Position 2 0) (Position 2 1))) Nothing "Syntax"]
expectDiagnostics [("Foo.daml", [(DsError, (2,0), "Parse error")])]
completions <- getCompletions foo (Position 2 6)
liftIO $ completions @?= [mkModuleCompletion "DA.Internal.RebindableSyntax" & detail .~ Nothing]
]
@ -882,7 +850,7 @@ multiPackageTests damlc
, "dependencies: [daml-prim, daml-stdlib]"
]
writeFileUTF8 (dir </> "a" </> "A.daml") $ unlines
[ "daml 1.2 module A where"
[ "module A where"
, "data A = A"
, "a = A"
]
@ -897,7 +865,7 @@ multiPackageTests damlc
, "dependencies: [daml-prim, daml-stdlib, " <> show (".." </> "a" </> "a.dar") <> "]"
]
writeFileUTF8 (dir </> "b" </> "B.daml") $ unlines
[ "daml 1.2 module B where"
[ "module B where"
, "import A"
, "f : Scenario A"
, "f = pure a"
@ -951,7 +919,7 @@ multiPackageTests damlc
, "dependencies: [daml-prim, daml-stdlib]"
]
writeFileUTF8 (dir </> "a" </> "A.daml") $ unlines
[ "daml 1.2 module A where"
[ "module A where"
, "data A = A"
, "a = A"
]
@ -966,7 +934,7 @@ multiPackageTests damlc
, "dependencies: [daml-prim, daml-stdlib, " <> show (".." </> "a" </> "a.dar") <> "]"
]
writeFileUTF8 (dir </> "b" </> "B.daml") $ unlines
[ "daml 1.2 module B where"
[ "module B where"
, "import A"
, "f : Scenario A"
, "f = pure a"

View File

@ -167,7 +167,6 @@ writeMinimalProject = do
, " - daml-stdlib"
]
writeFileUTF8 "Main.daml" $ unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "template T with p : Party where signatory p"
]

View File

@ -105,8 +105,7 @@ packagingTests = testGroup "packaging"
, " - daml-stdlib"
]
writeFileUTF8 (myDepDir </> "daml" </> "MyDep.daml") $ unlines
[ "daml 1.2"
, "module MyDep where"
[ "module MyDep where"
]
withCurrentDirectory myDepDir $ callCommandSilent "daml build -o mydep.dar"
let myTriggerDir = tmpDir </> "mytrigger"
@ -123,8 +122,7 @@ packagingTests = testGroup "packaging"
, " - " <> myDepDir </> "mydep.dar"
]
writeFileUTF8 (myTriggerDir </> "daml/Main.daml") $ unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "import MyDep ()"
, "import Daml.Trigger ()"
]
@ -216,8 +214,7 @@ packagingTests = testGroup "packaging"
, " - --wall-clock-time"
]
writeFileUTF8 (projDir </> "daml/Main.daml") $ unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "import Daml.Script"
, "template T with p : Party where signatory p"
, "init : Script ()"
@ -283,8 +280,7 @@ packagingTests = testGroup "packaging"
, " - daml-stdlib"
]
writeFileUTF8 (projDir </> "daml/Main.daml") $ unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "template T with p : Party where signatory p"
]
sandboxPort :: Int <- fromIntegral <$> getFreePort
@ -379,8 +375,7 @@ packagingTests = testGroup "packaging"
, " - daml-stdlib"
]
writeFileUTF8 (projDir </> "daml/Main.daml") $ unlines
[ "daml 1.2"
, "module Main where"
[ "module Main where"
, "template T with p : Party where signatory p"
]
sandboxPort :: Int <- fromIntegral <$> getFreePort

View File

@ -1,8 +1,6 @@
-- Copyright (c) 2020 Digital Asset (Switzerland) GmbH and/or its affiliates. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0
daml 1.2
module Examples where
nfib 0 = 1

View File

@ -1,7 +1,7 @@
-- Copyright (c) 2020 Digital Asset (Switzerland) GmbH and/or its affiliates. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0
daml 1.2 module Test where
module Test where
import qualified DA.Next.Set as S
import DA.Next.Set (Set)
@ -62,4 +62,3 @@ run = scenario do
_ <- submitMustFail bob $ exercise accepted LookupGivenKey with actor = bob, keyMaintainers = salice
pure ()

View File

@ -11,7 +11,6 @@ This page gives reference information on the structure of DAML files outside of
File structure
**************
- Language version (``daml 1.2``).
- This file's module name (``module NameOfThisFile where``).
Part of a hierarchical module system to facilitate code reuse. Must be the same as the DAML file name, without the file extension.

View File

@ -40,7 +40,7 @@ $ daml extractor --help
Trying it out
*************
This example extracts:
This example extracts:
- all contract data from the beginning of the ledger to the current latest transaction
- for the party ``Scrooge_McDuck``
@ -53,7 +53,7 @@ This example extracts:
$ daml extractor postgresql --user postgres --connecturl jdbc:postgresql:daml_export --party Scrooge_McDuck -h 192.168.1.12 -p 6865 --to head
This terminates after reaching the transaction which was the latest at the time the Extractor started streaming.
This terminates after reaching the transaction which was the latest at the time the Extractor started streaming.
To run the Extractor indefinitely, and thus keeping the database up to date as new transactions arrive on the ledger, omit the ``--to head`` parameter to fall back to the default streaming-indefinitely approach, or state explicitly by using the ``--to follow`` parameter.
@ -299,8 +299,8 @@ When updating packages, you can end up with multiple versions of the same packag
Lets say you have a template called ``My.Company.Finance.Account``::
daml 1.2 module My.Company.Finance.Account where
module My.Company.Finance.Account where
template Account
with
provider: Party
@ -314,8 +314,8 @@ This is built into a package with a resulting hash ``6021727fe0822d688ddd5459974
Later you add a new field, ``displayName``::
daml 1.2 module My.Company.Finance.Account where
module My.Company.Finance.Account where
template Account
with
provider: Party
@ -330,22 +330,22 @@ The hash of the new package with the update is ``1239d1c5df140425f01a5112325d2e4
There are contract instances of first version of the template which were created before the new field is added, and there are contract instances of the new version which were created since. Lets say you have one instance of each::
{
{
"owner":"Bob",
"provider":"Bob",
"accountId":"6021-5678",
"observers":[
"observers":[
"Alice"
]
}
and::
{
{
"owner":"Bob",
"provider":"Bob",
"accountId":"1239-4321",
"observers":[
"observers":[
"Alice"
],
"displayName":"Personal"
@ -359,7 +359,7 @@ They will look like this when extracted:
To have a consistent view of the two versions with a default value ``NULL`` for the missing field of instances of older versions, you can create a view which contains all ``Account`` rows::
CREATE VIEW account_view AS
SELECT
SELECT
create_arguments->>'owner' AS owner
,create_arguments->>'provider' AS provider
,create_arguments->>'accountId' AS accountId
@ -372,7 +372,7 @@ To have a consistent view of the two versions with a default value ``NULL`` for
AND
template = 'My.Company.Finance.Account'
UNION
SELECT
SELECT
create_arguments->>'owner' AS owner
,create_arguments->>'provider' AS provider
,create_arguments->>'accountId' AS accountId
@ -393,14 +393,14 @@ Then, ``account_view will`` contain both contract instances:
Logging
*******
By default, the Extractor logs to stderr, with INFO verbose level. To change the level, use the ``-DLOGLEVEL=[level]`` option, e.g. ``-DLOGLEVEL=TRACE``.
By default, the Extractor logs to stderr, with INFO verbose level. To change the level, use the ``-DLOGLEVEL=[level]`` option, e.g. ``-DLOGLEVEL=TRACE``.
You can supply your own logback configuration file via the standard method: https://logback.qos.ch/manual/configuration.html
Continuity
**********
When you terminate the Extractor and restart it, it will continue from where it left off. This happens because, when running, it saves its state into the ``state`` table in the ``public`` schema of the database. When started, it reads the contents of this table. If theres a saved state from a previous run, it restarts from where it left off. Theres no need to explicitly specify anything, this is done automatically.
When you terminate the Extractor and restart it, it will continue from where it left off. This happens because, when running, it saves its state into the ``state`` table in the ``public`` schema of the database. When started, it reads the contents of this table. If theres a saved state from a previous run, it restarts from where it left off. Theres no need to explicitly specify anything, this is done automatically.
DO NOT modify content of the ``state`` table. Doing so can result in the Extractor not being able to continue running against the database. If that happens, you must delete all data from the database and start again.
@ -411,7 +411,7 @@ The only parameters that you can change between two sessions running against the
Fault tolerance
***************
Once the Extractor connects to the Ledger Node and the database and creates the table structure from the fetched DAML packages, it wraps the transaction stream in a restart logic with an exponential backoff. This results in the Extractor not terminating even when the transaction stream is aborted for some reason (the ledger node is down, theres a network partition, etc.).
Once the Extractor connects to the Ledger Node and the database and creates the table structure from the fetched DAML packages, it wraps the transaction stream in a restart logic with an exponential backoff. This results in the Extractor not terminating even when the transaction stream is aborted for some reason (the ledger node is down, theres a network partition, etc.).
Once the connection is back, it continues the stream from where it left off. If it cant reach the node on the host/port pair the Extractor was started with, you need to manually stop it and restart with the updated address.
@ -422,7 +422,7 @@ Troubleshooting
Cant connect to the Ledger Node
================================
If the Extractor cant connect to the Ledger node on startup, youll see a message like this in the logs, and the Extractor will terminate::
16:47:51.208 ERROR c.d.e.Main$@[akka.actor.default-dispatcher-7] - FAILURE:

View File

@ -45,11 +45,11 @@ genrule(
filecount=32
outs=($(OUTS))
main="$${outs[0]}"
echo 'daml 1.2
echo '
module VeryLargeArchive.Blobs where
import VeryLargeArchive.Blob1()' > "$$main"
firstfil="$${outs[1]}"
echo 'daml 1.2
echo '
module VeryLargeArchive.Blob1 where
' > "$$firstfil"
{ for linen in `seq 1 1024`; do

View File

@ -1,7 +1,6 @@
-- Copyright (c) 2020 Digital Asset (Switzerland) GmbH and/or its affiliates. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0
daml 1.2
module PingPong where
template Ping