daml-doc improvements (#14867)

* Show "(no fields)" for fieldless records in daml-doc .rst output

* Update daml-test-files *.EXPECTED.rst

* Extract compareRendered from renderTest

* Add daml-doc test cases for renderFolder

* Add operator (DA.Daml.Doc.Render.Util.<->)

* Avoid trailing whitespace in daml-doc.{md,rst} output

* Update daml-test-files *.EXPECTED.{md,rst} and DA.Daml.Doc.Render.Tests

* Drop unused code

* Update comments

changelog_begin
changelog_end
This commit is contained in:
Moisés Ackerman 2022-09-02 16:24:59 +02:00 committed by GitHub
parent 3902380b14
commit b305f4111d
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
30 changed files with 572 additions and 465 deletions

View File

@ -6,7 +6,6 @@ module DA.Daml.Doc.Extract.Templates
, getTemplateData
, getInstanceDocs
, getInterfaceDocs
, stripInstanceSuffix
) where
import DA.Daml.Doc.Types as DDoc
@ -19,7 +18,6 @@ import Data.Maybe (fromMaybe, mapMaybe)
import Data.Tuple.Extra (second)
import qualified Data.Set as Set
import qualified Data.Text as T
import Data.Monoid (First (..))
import "ghc-lib" GHC
import "ghc-lib-parser" Var (varType)
@ -84,8 +82,8 @@ getInterfaceDocs DocCtx{..} typeMap interfaceInstanceMap =
ifADT = asADT typeMap name
choices = Set.toList . fromMaybe Set.empty $ MS.lookup name dc_choices
-- | Extracts all names of templates defined in a module,
-- and a map of template names to its set of choices
-- | Extracts all names of templates and interfaces defined in a module,
-- and a map of template/interface names to its set of choices
getTemplateData :: ParsedModule ->
( Set.Set Typename
, Set.Set Typename
@ -98,8 +96,7 @@ getTemplateData ParsedModule{..} =
interfaces = mapMaybe isInterface dataDs
choiceMap = MS.fromListWith (<>) $
map (second Set.singleton) $
mapMaybe isChoice instDs ++
mapMaybe isIfaceChoice instDs
mapMaybe isChoice instDs
in
(Set.fromList templates, Set.fromList interfaces, choiceMap)
where
@ -126,9 +123,9 @@ hasGhcTypesConstraint c decl
, occNameString cst == c = Just $ Typename $ packRdrName $ unLoc tcdLName
| otherwise = Nothing
-- | If the given instance declaration is declaring a template choice instance,
-- return template and choice name (IdP). Used to build the set of choices
-- per template declared in a module.
-- | If the given instance declaration is declaring a template/interface choice instance,
-- return template/interface and choice name (IdP). Used to build the set of choices
-- per template/interface declared in a module.
isChoice :: ClsInstDecl GhcPs -> Maybe (Typename, Typename)
isChoice (XClsInstDecl _) = Nothing
isChoice ClsInstDecl{..}
@ -150,51 +147,6 @@ isChoiceTy ty
| otherwise = Nothing
-- | If the given instance declaration is declaring an interface choice instance, return interface
-- name and choice name.
isIfaceChoice :: ClsInstDecl GhcPs -> Maybe (Typename, Typename)
isIfaceChoice (XClsInstDecl _) = Nothing
isIfaceChoice decl@ClsInstDecl{}
| Just (ifaceName, ty) <- hasImplementsConstraint decl
, Just (_templ, choiceName) <- isChoiceTy ty
= Just (Typename . packRdrName $ ifaceName, choiceName)
| otherwise = Nothing
-- | Matches on a DA.Internal.Desugar.Implements interface constraint in the context of the instance
-- declaration. Returns the interface name and the body of the instance in case the constraint is
-- present, else nothing.
hasImplementsConstraint :: ClsInstDecl GhcPs -> Maybe (RdrName, HsType GhcPs)
hasImplementsConstraint (XClsInstDecl _) = Nothing
hasImplementsConstraint ClsInstDecl{..} =
let (L _ ctxs, L _ ty) = splitLHsQualTy $ hsSigType cid_poly_ty
in (,ty) <$> getFirst (foldMap (First . getImplementsConstraint) ctxs)
-- | If the given type is a (DA.Internal.Desugar.Implements t I) constraint,
-- returns the name of I.
getImplementsConstraint :: LHsType GhcPs -> Maybe RdrName
getImplementsConstraint lctx
| L _ ctx <- dropParTy lctx
, HsAppTy _ (L _ app1) (L _ iface) <- ctx
, HsTyVar _ _ (L _ ifaceName) <- iface
, HsAppTy _ (L _ impl) (L _ _t) <- app1
, HsTyVar _ _ (L _ implCls) <- impl
, Qual implClsModule implClassOcc <- implCls
, moduleNameString implClsModule == "DA.Internal.Desugar"
, occNameString implClassOcc == "Implements"
= Just ifaceName
| otherwise = Nothing
-- | Removes any `HsParTy` constructors from an `LHsType a`.
dropParTy :: LHsType a -> LHsType a
dropParTy (L _ (HsParTy _ ty)) = dropParTy ty
dropParTy ty = ty
-- | Strip the @Instance@ suffix off of a typename, if it's there.
-- Otherwise returns 'Nothing'.
stripInstanceSuffix :: Typename -> Maybe Typename
stripInstanceSuffix (Typename t) = Typename <$> T.stripSuffix "Instance" t
-- | Get (normal) typeclass instances data.
getInstanceDocs :: DocCtx -> ClsInst -> InstanceDoc
getInstanceDocs ctx@DocCtx{dc_decls} ClsInst{..} =

View File

@ -7,6 +7,7 @@ module DA.Daml.Doc.Render
, RenderMode(..)
, renderDocs
, renderPage
, renderFolder
, renderRst
, renderMd
, renderModule

View File

@ -8,7 +8,7 @@ module DA.Daml.Doc.Render.Markdown
import DA.Daml.Doc.Anchor
import DA.Daml.Doc.Types
import DA.Daml.Doc.Render.Util (adjust, escapeText)
import DA.Daml.Doc.Render.Util (adjust, escapeText, (<->))
import DA.Daml.Doc.Render.Monoid
import Data.List.Extra
@ -17,8 +17,8 @@ import qualified Data.Text as T
renderMd :: RenderEnv -> RenderOut -> [T.Text]
renderMd env = \case
RenderSpaced chunks -> renderMdSpaced env chunks
RenderModuleHeader title -> ["# " <> title]
RenderSectionHeader title -> ["## " <> title]
RenderModuleHeader title -> ["#" <-> title]
RenderSectionHeader title -> ["##" <-> title]
RenderBlock block -> blockquote (renderMd env block)
RenderList items -> spaced (map (bullet . renderMd env) items)
RenderRecordFields fields -> renderMdFields env fields
@ -26,7 +26,7 @@ renderMd env = \case
RenderDocs docText -> T.lines . unDocText $ docText
RenderAnchor anchor -> [anchorTag anchor]
RenderIndex moduleNames ->
[ "* " <> renderMdLink env
[ "*" <-> renderMdLink env
(Reference Nothing (moduleAnchor moduleName))
(unModulename moduleName)
| moduleName <- moduleNames
@ -34,8 +34,8 @@ renderMd env = \case
renderMdWithAnchor :: RenderEnv -> Anchor -> RenderOut -> [T.Text]
renderMdWithAnchor env anchor = \case
RenderModuleHeader title -> ["# " <> anchorTag anchor <> title]
RenderSectionHeader title -> ["## " <> anchorTag anchor <> title]
RenderModuleHeader title -> ["#" <-> anchorTag anchor <> title]
RenderSectionHeader title -> ["##" <-> anchorTag anchor <> title]
RenderParagraph text -> [anchorTag anchor <> renderMdText env text]
other -> anchorTag anchor : renderMd env other
@ -78,14 +78,17 @@ spaced :: [[T.Text]] -> [T.Text]
spaced = intercalate [""]
blockquote :: [T.Text] -> [T.Text]
blockquote = map ("> " <>)
blockquote = map (">" <->)
indent :: [T.Text] -> [T.Text]
indent = map (" " <>)
indent = map indent1 where
indent1 t
| T.null t = ""
| otherwise = " " <> t
bullet :: [T.Text] -> [T.Text]
bullet [] = []
bullet (x : xs) = ("* " <> x) : indent xs
bullet (x : xs) = ("*" <-> x) : indent xs
escapeMd :: T.Text -> T.Text
escapeMd = escapeText (`elem` ("[]*_~`<>\\&" :: String))

View File

@ -9,7 +9,7 @@ module DA.Daml.Doc.Render.Rst
import DA.Daml.Doc.Types
import DA.Daml.Doc.Render.Monoid
import DA.Daml.Doc.Render.Util (escapeText)
import DA.Daml.Doc.Render.Util (escapeText, (<->))
import qualified Prettyprinter as Pretty
import Prettyprinter (Doc, defaultLayoutOptions, layoutPretty, pretty, (<+>))
@ -36,7 +36,7 @@ renderRst env = \case
[ ".. toctree::"
, " :maxdepth: 3"
, " :titlesonly:"
, " "
, ""
] ++
[ T.concat
[ " "
@ -100,11 +100,14 @@ spaced = intercalate [""] . respace
[] -> []
indent :: [T.Text] -> [T.Text]
indent = map (" " <>)
indent = map indent1 where
indent1 t
| T.null t = ""
| otherwise = " " <> t
bullet :: [T.Text] -> [T.Text]
bullet [] = []
bullet (x : xs) = ("+ " <> x) : indent xs
bullet (x : xs) = ("+" <-> x) : indent xs
header :: T.Text -> T.Text -> [T.Text]
header headerChar title =
@ -113,7 +116,7 @@ header headerChar title =
]
renderRstFields :: RenderEnv -> [(RenderText, RenderText, RenderText)] -> [T.Text]
renderRstFields _ [] = mempty
renderRstFields _ [] = ["(no fields)"]
renderRstFields env fields = concat
[ [ ".. list-table::"
, " :widths: 15 10 30"
@ -126,9 +129,9 @@ renderRstFields env fields = concat
]
where
fieldRows = concat
[ [ " * - " <> renderRstText env name
, " - " <> renderRstText env ty
, " - " <> renderRstText env doc ]
[ [ " * -" <-> renderRstText env name
, " -" <-> renderRstText env ty
, " -" <-> renderRstText env doc ]
| (name, ty, doc) <- fields
]

View File

@ -11,6 +11,7 @@ module DA.Daml.Doc.Render.Util
, inParens
, wrapOp
, escapeText
, (<->)
) where
import qualified Data.Text as T
@ -61,3 +62,11 @@ escapeText p = T.pack . concatMap escapeChar . T.unpack
escapeChar c
| p c = ['\\', c]
| otherwise = [c]
-- | Appends two texts with a space in between, unless one of the arguments is
-- empty, like '(Text.PrettyPrint.Annotated.Extended.<->)' but for 'T.Text'.
(<->) :: T.Text -> T.Text -> T.Text
l <-> r
| T.null l = r
| T.null r = l
| otherwise = T.concat [l, " ", r]

View File

@ -11,6 +11,9 @@ import DA.Daml.Doc.Render
import Control.Monad.Except
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import qualified Data.Map.Merge.Strict as Map.Merge
import qualified Test.Tasty.Extended as Tasty
import Test.Tasty.HUnit
@ -20,10 +23,26 @@ mkTestTree :: AnchorMap -> IO Tasty.TestTree
mkTestTree externalAnchors = do
pure $ Tasty.testGroup "DA.Daml.Doc.Render"
[ Tasty.testGroup "RST Rendering" $
zipWith (renderTest Rst externalAnchors) cases expectRst
zipWith (renderTest Rst externalAnchors) cases (expectRst False)
, Tasty.testGroup "Markdown Rendering" $
zipWith (renderTest Markdown externalAnchors) cases expectMarkdown
, Tasty.testGroup "RST Folder Rendering" $ pure $
renderFolderTest Rst externalAnchors folderTestCase expectRstFolder
, Tasty.testGroup "Markdown Folder Rendering" $ pure $
renderFolderTest Markdown externalAnchors folderTestCase expectMarkdownFolder
]
where
folderTestCase = ("Render folder", snd <$> cases)
expectRstFolder = mkExpectFolder expectRstIndex (expectRst True)
expectMarkdownFolder = mkExpectFolder expectMarkdownIndex expectMarkdown
mkExpectFolder expectIndex expectMods =
( expectIndex
, Map.fromList $
zipWith
(\(_, mod) expect -> (md_name mod, expect))
cases
expectMods
)
ctx0 :: Context
ctx0 = Context []
@ -84,24 +103,28 @@ cases = [ ("Empty module",
)
]
expectRst :: [T.Text]
expectRst =
expectRst ::
Bool
-- ^ If True, we are rendering the modules as a folder structure, so
-- the header underlines get bumped one level up ('^' => '-' => '=')
-> [T.Text]
expectRst asFolder =
[ T.empty
, mkExpectRst "module-typedef" "Typedef" "" [] []
, mkExpectRst asFolder "module-typedef" "Typedef" "" [] []
[ ".. _type-typedef-t:"
, ""
, "**type** `T <type-typedef-t_>`_ a"
, " \\= TT TTT"
, " "
, ""
, " T descr"
] []
, mkExpectRst "module-twotypes" "TwoTypes" "" []
, mkExpectRst asFolder "module-twotypes" "TwoTypes" "" []
[]
[ ".. _type-twotypes-t:"
, ""
, "**type** `T <type-twotypes-t_>`_ a"
, " \\= TT"
, " "
, ""
, " T descr"
, ""
, ".. _data-twotypes-d:"
@ -109,40 +132,40 @@ expectRst =
, "**data** `D <data-twotypes-d_>`_ d"
, ""
, " .. _constr-twotypes-d:"
, " "
, ""
, " `D <constr-twotypes-d_>`_ a"
, " "
, ""
, " D descr"
]
[]
, mkExpectRst "module-function1" "Function1" "" [] [] []
, mkExpectRst asFolder "module-function1" "Function1" "" [] [] []
[ ".. _function-function1-f:"
, ""
, "`f <function-function1-f_>`_"
, " \\: TheType"
, " "
, ""
, " the doc"
]
, mkExpectRst "module-function3" "Function3" "" [] [] []
, mkExpectRst asFolder "module-function3" "Function3" "" [] [] []
[ ".. _function-function3-f:"
, ""
, "`f <function-function3-f_>`_"
, " \\: TheType"
]
, mkExpectRst "module-onlyclass" "OnlyClass" ""
, mkExpectRst asFolder "module-onlyclass" "OnlyClass" ""
[]
[ ".. _class-onlyclass-c:"
, ""
, "**class** `C <class-onlyclass-c_>`_ a **where**"
, ""
, " .. _function-onlyclass-member:"
, " "
, ""
, " `member <function-onlyclass-member_>`_"
, " \\: a"
]
[]
[]
, mkExpectRst "module-multilinefield" "MultiLineField" ""
, mkExpectRst asFolder "module-multilinefield" "MultiLineField" ""
[]
[]
[ ".. _data-multilinefield-d:"
@ -150,13 +173,13 @@ expectRst =
, "**data** `D <data-multilinefield-d_>`_"
, ""
, " .. _constr-multilinefield-d:"
, " "
, ""
, " `D <constr-multilinefield-d_>`_"
, " "
, ""
, " .. list-table::"
, " :widths: 15 10 30"
, " :header-rows: 1"
, " "
, ""
, " * - Field"
, " - Type"
, " - Description"
@ -165,23 +188,33 @@ expectRst =
, " - This is a multiline field description"
]
[]
, mkExpectRst "module-functionctx" "FunctionCtx" "" [] [] []
, mkExpectRst asFolder "module-functionctx" "FunctionCtx" "" [] [] []
[ ".. _function-g:"
, ""
, "`g <function-g_>`_"
, " \\: Eq t \\=\\> t \\-\\> Bool"
, " "
, ""
, " function with context"
]
]
<> repeat (error "Missing expectation (Rst)")
mkExpectRst :: T.Text -> T.Text -> T.Text -> [T.Text] -> [T.Text] -> [T.Text] -> [T.Text] -> T.Text
mkExpectRst anchor name descr templates classes adts fcts = T.unlines . concat $
mkExpectRst ::
Bool
-- ^ If True, we are rendering the modules as a folder structure, so
-- the header underlines get bumped one level up ('^' => '-' => '=')
-> T.Text
-> T.Text
-> T.Text
-> [T.Text]
-> [T.Text]
-> [T.Text]
-> [T.Text]
-> T.Text
mkExpectRst asFolder anchor name descr templates classes adts fcts = T.unlines . concat $
[ [ ".. _" <> anchor <> ":"
, ""
, "Module " <> name
, "-------" <> T.replicate (T.length name) "-"
, h1 ("Module " <> name)
, ""
]
, if T.null descr then [] else [descr, ""]
@ -195,15 +228,31 @@ mkExpectRst anchor name descr templates classes adts fcts = T.unlines . concat $
if null docs
then []
else
[ title
, T.replicate (T.length title) "^"
[ h2 title
, ""
, T.unlines docs
, T.unlines docs -- NB T.unlines adds a trailing '\n'
, ""
]
h1 = headerOf (pick '=' '-')
h2 = headerOf (pick '-' '^')
pick x y = if asFolder then x else y
headerOf c t = t <> "\n" <> T.replicate (T.length t) (T.singleton c)
-- NB T.unlines adds a trailing '\n'
expectRstIndex :: T.Text
expectRstIndex = T.unlines
[ ".. toctree::"
, " :maxdepth: 3"
, " :titlesonly:"
, ""
, " Empty <Empty>"
, " Function1 <Function1>"
, " Function3 <Function3>"
, " FunctionCtx <FunctionCtx>"
, " MultiLineField <MultiLineField>"
, " OnlyClass <OnlyClass>"
, " TwoTypes <TwoTypes>"
, " Typedef <Typedef>"
]
expectMarkdown :: [T.Text]
expectMarkdown =
@ -212,7 +261,7 @@ expectMarkdown =
[ "<a name=\"type-typedef-t\"></a>**type** [T](#type-typedef-t) a"
, ""
, "> = TT TTT"
, "> "
, ">"
, "> T descr"
]
[]
@ -220,13 +269,13 @@ expectMarkdown =
[ "<a name=\"type-twotypes-t\"></a>**type** [T](#type-twotypes-t) a"
, ""
, "> = TT"
, "> "
, ">"
, "> T descr"
, ""
, "<a name=\"data-twotypes-d\"></a>**data** [D](#data-twotypes-d) d"
, ""
, "> <a name=\"constr-twotypes-d\"></a>[D](#constr-twotypes-d) a"
, "> "
, ">"
, "> > D descr"
]
[]
@ -234,7 +283,7 @@ expectMarkdown =
[ "<a name=\"function-function1-f\"></a>[f](#function-function1-f)"
, ""
, "> : TheType"
, "> "
, ">"
, "> the doc"
]
, mkExpectMD "module-function3" "Function3" "" [] [] []
@ -247,7 +296,7 @@ expectMarkdown =
[ "<a name=\"class-onlyclass-c\"></a>**class** [C](#class-onlyclass-c) a **where**"
, ""
, "> <a name=\"function-onlyclass-member\"></a>[member](#function-onlyclass-member)"
, "> "
, ">"
, "> > : a"
]
[]
@ -258,7 +307,7 @@ expectMarkdown =
[ "<a name=\"data-multilinefield-d\"></a>**data** [D](#data-multilinefield-d)"
, ""
, "> <a name=\"constr-multilinefield-d\"></a>[D](#constr-multilinefield-d)"
, "> "
, ">"
, "> > | Field | Type | Description |"
, "> > | :---- | :---- | :---------- |"
, "> > | f | T | This is a multiline field description |"
@ -268,7 +317,7 @@ expectMarkdown =
[ "<a name=\"function-g\"></a>[g](#function-g)"
, ""
, "> : Eq t =\\> t -\\> Bool"
, "> "
, ">"
, "> function with context"
]
]
@ -301,6 +350,18 @@ mkExpectMD anchor name descr templates classes adts fcts
, ""]
]
expectMarkdownIndex :: T.Text
expectMarkdownIndex = T.unlines
[ "* Empty"
, "* Function1"
, "* Function3"
, "* FunctionCtx"
, "* MultiLineField"
, "* OnlyClass"
, "* TwoTypes"
, "* Typedef"
]
renderTest :: RenderFormat -> AnchorMap -> (String, ModuleDoc) -> T.Text -> Tasty.TestTree
renderTest format externalAnchors (name, input) expected =
testCase name $ do
@ -311,7 +372,71 @@ renderTest format externalAnchors (name, input) expected =
Html -> error "HTML testing not supported (use Markdown)"
output = T.strip $ renderer input
expect = T.strip expected
compareRendered output expect
renderFolderTest ::
RenderFormat
-> AnchorMap
-> (String, [ModuleDoc])
-> (T.Text, Map Modulename T.Text)
-> Tasty.TestTree
renderFolderTest format externalAnchors (name, input) expected =
testCaseSteps name $ \step -> do
let
modStep modName =
step ("Checking module '" <> T.unpack (unModulename modName) <> "'")
unexpectedMod modName output = do
modStep modName
T.putStrLn $ T.unlines
[ "Unexpected module in output:"
, "Expected: <nothing>"
, "Actual:"
, T.pack $ show output ]
assertFailure "Unexpected module in output."
missingMod modName expect = do
modStep modName
T.putStrLn $ T.unlines
[ "Expected module missing from output:"
, "Expected:"
, T.pack $ show expect
, "Actual: <nothing>" ]
assertFailure "Expected module missing from output."
compareMod modName output expect = do
modStep modName
compareRendered output expect
void $ Map.Merge.mergeA
(Map.Merge.traverseMissing unexpectedMod)
(Map.Merge.traverseMissing missingMod)
(Map.Merge.zipWithAMatched compareMod)
outputModules
expectModules
step "Checking index"
compareRendered outputIndex expectIndex
where
(outputIndex, outputModules) = strip $ renderer input
(expectIndex, expectModules) = strip expected
renderer = case format of
Rst -> renderFolder renderRst externalAnchors . renderMap
Markdown -> renderFolder renderMd externalAnchors . renderMap
Html -> error "HTML testing not supported (use Markdown)"
renderMap mods = Map.fromList
[ (md_name mod, renderModule mod)
| mod <- mods
]
strip (index, modMap) =
(T.strip index, T.strip <$> modMap)
compareRendered :: T.Text -> T.Text -> IO ()
compareRendered output expect = do
unless (output == expect) $ do
T.putStrLn $ T.unlines
[ "Output differs from expectation:"

View File

@ -8,9 +8,9 @@ not present in the class itself.
<a name="class-constrainedclassmethod-a-38747"></a>**class** [A](#class-constrainedclassmethod-a-38747) t **where**
> <a name="function-constrainedclassmethod-foo-16027"></a>[foo](#function-constrainedclassmethod-foo-16027)
>
>
> > : t -\> t
>
>
> <a name="function-constrainedclassmethod-bar-5816"></a>[bar](#function-constrainedclassmethod-bar-5816)
>
>
> > : [Eq](https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-classes-eq-22713) t =\> t -\> t

View File

@ -14,11 +14,11 @@ Typeclasses
**class** `A <class-constrainedclassmethod-a-38747_>`_ t **where**
.. _function-constrainedclassmethod-foo-16027:
`foo <function-constrainedclassmethod-foo-16027_>`_
\: t \-\> t
.. _function-constrainedclassmethod-bar-5816:
`bar <function-constrainedclassmethod-bar-5816_>`_
\: `Eq <https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-classes-eq-22713>`_ t \=\> t \-\> t

View File

@ -9,9 +9,9 @@ Testing the daml version header.
> | Field | Type | Description |
> | :-------------------------------------------------------------------------------------- | :-------------------------------------------------------------------------------------- | :---------- |
> | p | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
>
>
> * **Choice Archive**
>
>
> (no fields)
## Functions

View File

@ -5,49 +5,49 @@
<a name="class-defaultmethods-d-39130"></a>**class** [D](#class-defaultmethods-d-39130) a **where**
> <a name="function-defaultmethods-x-53637"></a>[x](#function-defaultmethods-x-53637)
>
>
> > : a
>
>
> <a name="function-defaultmethods-y-51560"></a>[y](#function-defaultmethods-y-51560)
>
>
> > : a
<a name="class-defaultmethods-foldablex-43965"></a>**class** [FoldableX](#class-defaultmethods-foldablex-43965) t **where**
> <a name="function-defaultmethods-foldrx-50503"></a>[foldrX](#function-defaultmethods-foldrx-50503)
>
>
> > : (a -\> b -\> b) -\> b -\> t a -\> b
<a name="class-defaultmethods-traversablex-84604"></a>**class** ([Functor](https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-base-functor-31205) t, [FoldableX](#class-defaultmethods-foldablex-43965) t) =\> [TraversableX](#class-defaultmethods-traversablex-84604) t **where**
> <a name="function-defaultmethods-traversex-89947"></a>[traverseX](#function-defaultmethods-traversex-89947)
>
>
> > : [Applicative](https://docs.daml.com/daml/stdlib/Prelude.html#class-da-internal-prelude-applicative-9257) m =\> (a -\> m b) -\> t a -\> m (t b)
>
>
> <a name="function-defaultmethods-sequencex-92456"></a>[sequenceX](#function-defaultmethods-sequencex-92456)
>
>
> > : [Applicative](https://docs.daml.com/daml/stdlib/Prelude.html#class-da-internal-prelude-applicative-9257) m =\> t (m a) -\> m (t a)
<a name="class-defaultmethods-id-10050"></a>**class** [Id](#class-defaultmethods-id-10050) a **where**
> <a name="function-defaultmethods-id-52623"></a>[id](#function-defaultmethods-id-52623)
>
>
> > : a -\> a
>
>
> **instance** [Id](#class-defaultmethods-id-10050) [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261)
<a name="class-defaultmethods-myshow-63060"></a>**class** [MyShow](#class-defaultmethods-myshow-63060) t **where**
> Default implementation with a separate type signature for the default method.
>
>
> <a name="function-defaultmethods-myshow-32065"></a>[myShow](#function-defaultmethods-myshow-32065)
>
>
> > : t -\> [Text](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-text-51952)
> >
> >
> > Doc for method.
>
>
> **default** myShow
>
>
> > : [Show](https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-show-show-65360) t =\> t -\> [Text](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-text-51952)
> >
> >
> > Doc for default.

View File

@ -11,12 +11,12 @@ Typeclasses
**class** `D <class-defaultmethods-d-39130_>`_ a **where**
.. _function-defaultmethods-x-53637:
`x <function-defaultmethods-x-53637_>`_
\: a
.. _function-defaultmethods-y-51560:
`y <function-defaultmethods-y-51560_>`_
\: a
@ -25,7 +25,7 @@ Typeclasses
**class** `FoldableX <class-defaultmethods-foldablex-43965_>`_ t **where**
.. _function-defaultmethods-foldrx-50503:
`foldrX <function-defaultmethods-foldrx-50503_>`_
\: (a \-\> b \-\> b) \-\> b \-\> t a \-\> b
@ -34,12 +34,12 @@ Typeclasses
**class** (`Functor <https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-base-functor-31205>`_ t, `FoldableX <class-defaultmethods-foldablex-43965_>`_ t) \=\> `TraversableX <class-defaultmethods-traversablex-84604_>`_ t **where**
.. _function-defaultmethods-traversex-89947:
`traverseX <function-defaultmethods-traversex-89947_>`_
\: `Applicative <https://docs.daml.com/daml/stdlib/Prelude.html#class-da-internal-prelude-applicative-9257>`_ m \=\> (a \-\> m b) \-\> t a \-\> m (t b)
.. _function-defaultmethods-sequencex-92456:
`sequenceX <function-defaultmethods-sequencex-92456_>`_
\: `Applicative <https://docs.daml.com/daml/stdlib/Prelude.html#class-da-internal-prelude-applicative-9257>`_ m \=\> t (m a) \-\> m (t a)
@ -48,10 +48,10 @@ Typeclasses
**class** `Id <class-defaultmethods-id-10050_>`_ a **where**
.. _function-defaultmethods-id-52623:
`id <function-defaultmethods-id-52623_>`_
\: a \-\> a
**instance** `Id <class-defaultmethods-id-10050_>`_ `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
.. _class-defaultmethods-myshow-63060:
@ -59,16 +59,16 @@ Typeclasses
**class** `MyShow <class-defaultmethods-myshow-63060_>`_ t **where**
Default implementation with a separate type signature for the default method\.
.. _function-defaultmethods-myshow-32065:
`myShow <function-defaultmethods-myshow-32065_>`_
\: t \-\> `Text <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-text-51952>`_
Doc for method\.
**default** myShow
\: `Show <https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-show-show-65360>`_ t \=\> t \-\> `Text <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-text-51952>`_
Doc for default\.

View File

@ -5,27 +5,27 @@
<a name="type-deriving-formula-60264"></a>**data** [Formula](#type-deriving-formula-60264) t
> <a name="constr-deriving-tautology-1247"></a>[Tautology](#constr-deriving-tautology-1247)
>
>
>
>
> <a name="constr-deriving-contradiction-64078"></a>[Contradiction](#constr-deriving-contradiction-64078)
>
>
>
>
> <a name="constr-deriving-proposition-76435"></a>[Proposition](#constr-deriving-proposition-76435) t
>
>
>
>
> <a name="constr-deriving-negation-39767"></a>[Negation](#constr-deriving-negation-39767) ([Formula](#type-deriving-formula-60264) t)
>
>
>
>
> <a name="constr-deriving-conjunction-55851"></a>[Conjunction](#constr-deriving-conjunction-55851) \[[Formula](#type-deriving-formula-60264) t\]
>
>
>
>
> <a name="constr-deriving-disjunction-19371"></a>[Disjunction](#constr-deriving-disjunction-19371) \[[Formula](#type-deriving-formula-60264) t\]
>
>
>
>
> **instance** [Functor](https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-base-functor-31205) [Formula](#type-deriving-formula-60264)
>
>
> **instance** [Eq](https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-classes-eq-22713) t =\> [Eq](https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-classes-eq-22713) ([Formula](#type-deriving-formula-60264) t)
>
>
> **instance** [Ord](https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-classes-ord-6395) t =\> [Ord](https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-classes-ord-6395) ([Formula](#type-deriving-formula-60264) t)
>
>
> **instance** [Show](https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-show-show-65360) t =\> [Show](https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-show-show-65360) ([Formula](#type-deriving-formula-60264) t)

View File

@ -11,39 +11,39 @@ Data Types
**data** `Formula <type-deriving-formula-60264_>`_ t
.. _constr-deriving-tautology-1247:
`Tautology <constr-deriving-tautology-1247_>`_
.. _constr-deriving-contradiction-64078:
`Contradiction <constr-deriving-contradiction-64078_>`_
.. _constr-deriving-proposition-76435:
`Proposition <constr-deriving-proposition-76435_>`_ t
.. _constr-deriving-negation-39767:
`Negation <constr-deriving-negation-39767_>`_ (`Formula <type-deriving-formula-60264_>`_ t)
.. _constr-deriving-conjunction-55851:
`Conjunction <constr-deriving-conjunction-55851_>`_ \[`Formula <type-deriving-formula-60264_>`_ t\]
.. _constr-deriving-disjunction-19371:
`Disjunction <constr-deriving-disjunction-19371_>`_ \[`Formula <type-deriving-formula-60264_>`_ t\]
**instance** `Functor <https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-base-functor-31205>`_ `Formula <type-deriving-formula-60264_>`_
**instance** `Eq <https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-classes-eq-22713>`_ t \=\> `Eq <https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-classes-eq-22713>`_ (`Formula <type-deriving-formula-60264_>`_ t)
**instance** `Ord <https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-classes-ord-6395>`_ t \=\> `Ord <https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-classes-ord-6395>`_ (`Formula <type-deriving-formula-60264_>`_ t)
**instance** `Show <https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-show-show-65360>`_ t \=\> `Show <https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-show-show-65360>`_ (`Formula <type-deriving-formula-60264_>`_ t)

View File

@ -8,13 +8,13 @@
> | :-------------------------------------------------------------------------------------- | :-------------------------------------------------------------------------------------- | :---------- |
> | tfield0 | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
> | tfield0' | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
>
>
> * **Choice Archive**
>
>
> (no fields)
>
>
> * **Choice Choice0**
>
>
> (no fields)
<a name="type-exportlist-template1-69519"></a>**template** [Template1](#type-exportlist-template1-69519)
@ -23,13 +23,13 @@
> | :-------------------------------------------------------------------------------------- | :-------------------------------------------------------------------------------------- | :---------- |
> | tfield1 | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
> | tfield1' | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
>
>
> * **Choice Archive**
>
>
> (no fields)
>
>
> * **Choice Choice1**
>
>
> (no fields)
<a name="type-exportlist-template2-27508"></a>**template** [Template2](#type-exportlist-template2-27508)
@ -38,13 +38,13 @@
> | :-------------------------------------------------------------------------------------- | :-------------------------------------------------------------------------------------- | :---------- |
> | tfield2 | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
> | tfield2' | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
>
>
> * **Choice Archive**
>
>
> (no fields)
>
>
> * **Choice Choice2**
>
>
> (no fields)
<a name="type-exportlist-template3-29585"></a>**template** [Template3](#type-exportlist-template3-29585)
@ -53,13 +53,13 @@
> | :-------------------------------------------------------------------------------------- | :-------------------------------------------------------------------------------------- | :---------- |
> | tfield3 | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
> | tfield3' | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
>
>
> * **Choice Archive**
>
>
> (no fields)
>
>
> * **Choice Choice3**
>
>
> (no fields)
## Typeclasses
@ -73,17 +73,17 @@
<a name="class-exportlist-class3-68865"></a>**class** [Class3](#class-exportlist-class3-68865) t **where**
> <a name="function-exportlist-member3-18707"></a>[member3](#function-exportlist-member3-18707)
>
>
> > : t
<a name="class-exportlist-class4-14138"></a>**class** [Class4](#class-exportlist-class4-14138) t **where**
> <a name="function-exportlist-member4-25320"></a>[member4](#function-exportlist-member4-25320)
>
>
> > : t
>
>
> <a name="function-exportlist-member4tick-39232"></a>[member4'](#function-exportlist-member4tick-39232)
>
>
> > : t
## Data Types
@ -99,9 +99,9 @@
<a name="type-exportlist-data3-37219"></a>**data** [Data3](#type-exportlist-data3-37219)
> <a name="constr-exportlist-constr3-11999"></a>[Constr3](#constr-exportlist-constr3-11999)
>
>
> > (no fields)
>
>
> **instance** [HasField](https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839) "field3" [Data3](#type-exportlist-data3-37219) [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261)
<a name="type-exportlist-data4-52140"></a>**data** [Data4](#type-exportlist-data4-52140)
@ -111,24 +111,24 @@
<a name="type-exportlist-data5-28529"></a>**data** [Data5](#type-exportlist-data5-28529)
> <a name="constr-exportlist-constr5-98773"></a>[Constr5](#constr-exportlist-constr5-98773)
>
>
> > | Field | Type | Description |
> > | :----------------------------------------------------------------------------- | :----------------------------------------------------------------------------- | :---------- |
> > | field5 | [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) | |
>
>
> **instance** [HasField](https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839) "field5" [Data5](#type-exportlist-data5-28529) [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261)
<a name="type-exportlist-data6-43450"></a>**data** [Data6](#type-exportlist-data6-43450)
> <a name="constr-exportlist-constr6-5386"></a>[Constr6](#constr-exportlist-constr6-5386)
>
>
> > | Field | Type | Description |
> > | :----------------------------------------------------------------------------- | :----------------------------------------------------------------------------- | :---------- |
> > | field6 | [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) | |
>
>
> <a name="constr-exportlist-constr6tick-99942"></a>[Constr6'](#constr-exportlist-constr6tick-99942)
>
>
>
>
> **instance** [HasField](https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839) "field6" [Data6](#type-exportlist-data6-43450) [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261)
## Functions

View File

@ -13,22 +13,24 @@ Templates
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - tfield0
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
* - tfield0'
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
+ **Choice Archive**
(no fields)
+ **Choice Choice0**
(no fields)
.. _type-exportlist-template1-69519:
@ -37,22 +39,24 @@ Templates
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - tfield1
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
* - tfield1'
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
+ **Choice Archive**
(no fields)
+ **Choice Choice1**
(no fields)
.. _type-exportlist-template2-27508:
@ -61,22 +65,24 @@ Templates
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - tfield2
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
* - tfield2'
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
+ **Choice Archive**
(no fields)
+ **Choice Choice2**
(no fields)
.. _type-exportlist-template3-29585:
@ -85,22 +91,24 @@ Templates
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - tfield3
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
* - tfield3'
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
+ **Choice Archive**
(no fields)
+ **Choice Choice3**
(no fields)
Typeclasses
^^^^^^^^^^^
@ -120,7 +128,7 @@ Typeclasses
**class** `Class3 <class-exportlist-class3-68865_>`_ t **where**
.. _function-exportlist-member3-18707:
`member3 <function-exportlist-member3-18707_>`_
\: t
@ -129,12 +137,12 @@ Typeclasses
**class** `Class4 <class-exportlist-class4-14138_>`_ t **where**
.. _function-exportlist-member4-25320:
`member4 <function-exportlist-member4-25320_>`_
\: t
.. _function-exportlist-member4tick-39232:
`member4' <function-exportlist-member4tick-39232_>`_
\: t
@ -158,10 +166,11 @@ Data Types
**data** `Data3 <type-exportlist-data3-37219_>`_
.. _constr-exportlist-constr3-11999:
`Constr3 <constr-exportlist-constr3-11999_>`_
(no fields)
**instance** `HasField <https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839>`_ \"field3\" `Data3 <type-exportlist-data3-37219_>`_ `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
.. _type-exportlist-data4-52140:
@ -175,20 +184,20 @@ Data Types
**data** `Data5 <type-exportlist-data5-28529_>`_
.. _constr-exportlist-constr5-98773:
`Constr5 <constr-exportlist-constr5-98773_>`_
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - field5
- `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
-
-
**instance** `HasField <https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839>`_ \"field5\" `Data5 <type-exportlist-data5-28529_>`_ `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
.. _type-exportlist-data6-43450:
@ -196,25 +205,25 @@ Data Types
**data** `Data6 <type-exportlist-data6-43450_>`_
.. _constr-exportlist-constr6-5386:
`Constr6 <constr-exportlist-constr6-5386_>`_
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - field6
- `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
-
-
.. _constr-exportlist-constr6tick-99942:
`Constr6' <constr-exportlist-constr6tick-99942_>`_
**instance** `HasField <https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839>`_ \"field6\" `Data6 <type-exportlist-data6-43450_>`_ `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
Functions

View File

@ -9,9 +9,9 @@
> | issuer | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
> | owner | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
> | amount | [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) | |
>
>
> * **Choice Archive**
>
>
> (no fields)
> * **interface instance** [Token](#type-interface-token-10651) **for** [Asset](#type-interface-asset-25340)
@ -21,47 +21,47 @@
<a name="type-interface-token-10651"></a>**interface** [Token](#type-interface-token-10651)
> An interface comment.
>
>
> **viewtype** [EmptyInterfaceView](#type-interface-emptyinterfaceview-28816)
>
>
> * **Choice GetRich**
>
>
> | Field | Type | Description |
> | :----------------------------------------------------------------------------- | :----------------------------------------------------------------------------- | :---------- |
> | byHowMuch | [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) | |
>
>
> * **Choice Noop**
>
>
> | Field | Type | Description |
> | :------ | :------ | :---------- |
> | nothing | () | |
>
>
> * **Choice Split**
>
>
> An interface choice comment.
>
>
> | Field | Type | Description |
> | :----------------------------------------------------------------------------- | :----------------------------------------------------------------------------- | :---------- |
> | splitAmount | [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) | A choice field comment. |
>
>
> * **Choice Transfer**
>
>
> | Field | Type | Description |
> | :-------------------------------------------------------------------------------------- | :-------------------------------------------------------------------------------------- | :---------- |
> | newOwner | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
>
>
> * **Method getAmount :** [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261)
>
>
> * **Method getOwner :** [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932)
>
>
> A method comment.
>
>
> * **Method noopImpl :** () -\> [Update](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072) ()
>
>
> * **Method setAmount :** [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) -\> [Token](#type-interface-token-10651)
>
>
> * **Method splitImpl :** [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) -\> [Update](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072) ([ContractId](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282) [Token](#type-interface-token-10651), [ContractId](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282) [Token](#type-interface-token-10651))
>
>
> * **Method transferImpl :** [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) -\> [Update](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072) ([ContractId](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282) [Token](#type-interface-token-10651))
## Data Types
@ -69,9 +69,9 @@
<a name="type-interface-emptyinterfaceview-28816"></a>**data** [EmptyInterfaceView](#type-interface-emptyinterfaceview-28816)
> <a name="constr-interface-emptyinterfaceview-1101"></a>[EmptyInterfaceView](#constr-interface-emptyinterfaceview-1101)
>
>
> > (no fields)
>
>
> **instance** [HasInterfaceView](https://docs.daml.com/daml/stdlib/Prelude.html#class-da-internal-interface-hasinterfaceview-4492) [Token](#type-interface-token-10651) [EmptyInterfaceView](#type-interface-emptyinterfaceview-28816)
## Functions

View File

@ -13,22 +13,23 @@ Templates
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - issuer
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
* - owner
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
* - amount
- `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
-
-
+ **Choice Archive**
(no fields)
+ **interface instance** `Token <type-interface-token-10651_>`_ **for** `Asset <type-interface-asset-25340_>`_
@ -40,75 +41,75 @@ Interfaces
**interface** `Token <type-interface-token-10651_>`_
An interface comment\.
**viewtype** `EmptyInterfaceView <type-interface-emptyinterfaceview-28816_>`_
+ **Choice GetRich**
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - byHowMuch
- `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
-
-
+ **Choice Noop**
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - nothing
- ()
-
-
+ **Choice Split**
An interface choice comment\.
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - splitAmount
- `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
- A choice field comment\.
+ **Choice Transfer**
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - newOwner
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
+ **Method getAmount \:** `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
+ **Method getOwner \:** `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
A method comment\.
+ **Method noopImpl \:** () \-\> `Update <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072>`_ ()
+ **Method setAmount \:** `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_ \-\> `Token <type-interface-token-10651_>`_
+ **Method splitImpl \:** `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_ \-\> `Update <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072>`_ (`ContractId <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282>`_ `Token <type-interface-token-10651_>`_, `ContractId <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282>`_ `Token <type-interface-token-10651_>`_)
+ **Method transferImpl \:** `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_ \-\> `Update <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072>`_ (`ContractId <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282>`_ `Token <type-interface-token-10651_>`_)
Data Types
@ -119,10 +120,11 @@ Data Types
**data** `EmptyInterfaceView <type-interface-emptyinterfaceview-28816_>`_
.. _constr-interface-emptyinterfaceview-1101:
`EmptyInterfaceView <constr-interface-emptyinterfaceview-1101_>`_
(no fields)
**instance** `HasInterfaceView <https://docs.daml.com/daml/stdlib/Prelude.html#class-da-internal-interface-hasinterfaceview-4492>`_ `Token <type-interface-token-10651_>`_ `EmptyInterfaceView <type-interface-emptyinterfaceview-28816_>`_
Functions

View File

@ -11,35 +11,35 @@
> | currency | [Text](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-text-51952) | only 3-letter symbols are allowed |
> | amount | [Decimal](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-decimal-18135) | must be positive |
> | regulators | \[[Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932)\] | `regulators` may observe any use of the `Iou` |
>
>
> * **Choice Archive**
>
>
> (no fields)
>
>
> * **Choice DoNothing**
>
>
> (no fields)
>
>
> * **Choice Merge**
>
>
> merges two "compatible" `Iou`s
>
>
> | Field | Type | Description |
> | :----------------------------------------------------------------------------------------------------------------------------- | :----------------------------------------------------------------------------------------------------------------------------- | :---------- |
> | otherCid | [ContractId](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282) [Iou](#type-iou12-iou-72962) | Must have same owner, issuer, and currency. The regulators may differ, and are taken from the original `Iou`. |
>
>
> * **Choice Split**
>
>
> splits into two `Iou`s with smaller amounts
>
>
> | Field | Type | Description |
> | :------------------------------------------------------------------------------------- | :------------------------------------------------------------------------------------- | :---------- |
> | splitAmount | [Decimal](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-decimal-18135) | must be between zero and original amount |
>
>
> * **Choice Transfer**
>
>
> changes the owner
>
>
> | Field | Type | Description |
> | :-------------------------------------------------------------------------------------- | :-------------------------------------------------------------------------------------- | :---------- |
> | newOwner | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
@ -49,7 +49,7 @@
<a name="function-iou12-main-28537"></a>[main](#function-iou12-main-28537)
> : [Scenario](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-scenario-98127) ()
>
>
> A single test scenario covering all functionality that `Iou` implements.
> This description contains [a link](http://example.com), some bogus <inline html>,
> and words_ with_ underscore, to test damldoc capabilities.

View File

@ -13,16 +13,16 @@ Templates
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - issuer
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
* - owner
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
* - currency
- `Text <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-text-51952>`_
- only 3\-letter symbols are allowed
@ -32,57 +32,59 @@ Templates
* - regulators
- \[`Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_\]
- ``regulators`` may observe any use of the ``Iou``
+ **Choice Archive**
(no fields)
+ **Choice DoNothing**
(no fields)
+ **Choice Merge**
merges two \"compatible\" ``Iou``s
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - otherCid
- `ContractId <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282>`_ `Iou <type-iou12-iou-72962_>`_
- Must have same owner, issuer, and currency\. The regulators may differ, and are taken from the original ``Iou``\.
+ **Choice Split**
splits into two ``Iou``s with smaller amounts
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - splitAmount
- `Decimal <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-decimal-18135>`_
- must be between zero and original amount
+ **Choice Transfer**
changes the owner
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - newOwner
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
Functions
^^^^^^^^^
@ -91,7 +93,7 @@ Functions
`main <function-iou12-main-28537_>`_
\: `Scenario <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-scenario-98127>`_ ()
A single test scenario covering all functionality that ``Iou`` implements\.
This description contains a link(http://example.com), some bogus \<inline html\>,
and words\_ with\_ underscore, to test damldoc capabilities\.

View File

@ -7,13 +7,13 @@ Test multiple names sharing the same type signature.
<a name="class-multiplenames-foo-41670"></a>**class** [Foo](#class-multiplenames-foo-41670) t **where**
> <a name="function-multiplenames-foo1-63639"></a>[foo1](#function-multiplenames-foo1-63639)
>
>
> > : t
> >
> >
> > This documentation is duplicated.
>
>
> <a name="function-multiplenames-foo2-604"></a>[foo2](#function-multiplenames-foo2-604)
>
>
> > : t
> >
> >
> > This documentation is duplicated.

View File

@ -13,15 +13,15 @@ Typeclasses
**class** `Foo <class-multiplenames-foo-41670_>`_ t **where**
.. _function-multiplenames-foo1-63639:
`foo1 <function-multiplenames-foo1-63639_>`_
\: t
This documentation is duplicated\.
.. _function-multiplenames-foo2-604:
`foo2 <function-multiplenames-foo2-604_>`_
\: t
This documentation is duplicated\.

View File

@ -5,11 +5,11 @@
<a name="type-newtype-nat-87202"></a>**data** [Nat](#type-newtype-nat-87202)
> <a name="constr-newtype-nat-30825"></a>[Nat](#constr-newtype-nat-30825)
>
>
> > | Field | Type | Description |
> > | :----------------------------------------------------------------------------- | :----------------------------------------------------------------------------- | :---------- |
> > | unNat | [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) | |
>
>
> **instance** [HasField](https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839) "unNat" [Nat](#type-newtype-nat-87202) [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261)
## Functions

View File

@ -11,20 +11,20 @@ Data Types
**data** `Nat <type-newtype-nat-87202_>`_
.. _constr-newtype-nat-30825:
`Nat <constr-newtype-nat-30825_>`_
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - unNat
- `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
-
-
**instance** `HasField <https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839>`_ \"unNat\" `Nat <type-newtype-nat-87202_>`_ `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
Functions

View File

@ -9,9 +9,9 @@
> | issuer | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
> | owner | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
> | amount | [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) | |
>
>
> * **Choice Archive**
>
>
> (no fields)
> * **interface instance** Token **for** [Asset](#type-qualifiedinterface-asset-82061)

View File

@ -13,21 +13,22 @@ Templates
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - issuer
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
* - owner
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
* - amount
- `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
-
-
+ **Choice Archive**
(no fields)
+ **interface instance** Token **for** `Asset <type-qualifiedinterface-asset-82061_>`_

View File

@ -5,39 +5,39 @@
<a name="type-qualifiedretroactiveinterfaceinstance-token-43978"></a>**interface** [Token](#type-qualifiedretroactiveinterfaceinstance-token-43978)
> **viewtype** [TokenView](#type-qualifiedretroactiveinterfaceinstance-tokenview-25557)
>
>
> * **Choice GetRich**
>
>
> | Field | Type | Description |
> | :----------------------------------------------------------------------------- | :----------------------------------------------------------------------------- | :---------- |
> | byHowMuch | [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) | |
>
>
> * **Choice Noop**
>
>
> | Field | Type | Description |
> | :------ | :------ | :---------- |
> | nothing | () | |
>
>
> * **Choice Split**
>
>
> An interface choice comment.
>
>
> | Field | Type | Description |
> | :----------------------------------------------------------------------------- | :----------------------------------------------------------------------------- | :---------- |
> | splitAmount | [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) | A choice field comment. |
>
>
> * **Choice Transfer**
>
>
> | Field | Type | Description |
> | :-------------------------------------------------------------------------------------- | :-------------------------------------------------------------------------------------- | :---------- |
> | newOwner | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
>
>
> * **Method noopImpl :** () -\> [Update](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072) ()
>
>
> * **Method setAmount :** [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) -\> [Token](#type-qualifiedretroactiveinterfaceinstance-token-43978)
>
>
> * **Method splitImpl :** [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) -\> [Update](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072) ([ContractId](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282) [Token](#type-qualifiedretroactiveinterfaceinstance-token-43978), [ContractId](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282) [Token](#type-qualifiedretroactiveinterfaceinstance-token-43978))
>
>
> * **Method transferImpl :** [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) -\> [Update](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072) ([ContractId](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282) [Token](#type-qualifiedretroactiveinterfaceinstance-token-43978))
> * **interface instance** [Token](#type-qualifiedretroactiveinterfaceinstance-token-43978) **for** Asset
@ -47,16 +47,16 @@
<a name="type-qualifiedretroactiveinterfaceinstance-tokenview-25557"></a>**data** [TokenView](#type-qualifiedretroactiveinterfaceinstance-tokenview-25557)
> <a name="constr-qualifiedretroactiveinterfaceinstance-tokenview-72346"></a>[TokenView](#constr-qualifiedretroactiveinterfaceinstance-tokenview-72346)
>
>
> > | Field | Type | Description |
> > | :-------------------------------------------------------------------------------------- | :-------------------------------------------------------------------------------------- | :---------- |
> > | owner | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
> > | amount | [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) | |
>
>
> **instance** [HasInterfaceView](https://docs.daml.com/daml/stdlib/Prelude.html#class-da-internal-interface-hasinterfaceview-4492) [Token](#type-qualifiedretroactiveinterfaceinstance-token-43978) [TokenView](#type-qualifiedretroactiveinterfaceinstance-tokenview-25557)
>
>
> **instance** [HasField](https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839) "amount" [TokenView](#type-qualifiedretroactiveinterfaceinstance-tokenview-25557) [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261)
>
>
> **instance** [HasField](https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839) "owner" [TokenView](#type-qualifiedretroactiveinterfaceinstance-tokenview-25557) [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932)
## Functions

View File

@ -11,67 +11,67 @@ Interfaces
**interface** `Token <type-qualifiedretroactiveinterfaceinstance-token-43978_>`_
**viewtype** `TokenView <type-qualifiedretroactiveinterfaceinstance-tokenview-25557_>`_
+ **Choice GetRich**
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - byHowMuch
- `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
-
-
+ **Choice Noop**
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - nothing
- ()
-
-
+ **Choice Split**
An interface choice comment\.
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - splitAmount
- `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
- A choice field comment\.
+ **Choice Transfer**
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - newOwner
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
+ **Method noopImpl \:** () \-\> `Update <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072>`_ ()
+ **Method setAmount \:** `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_ \-\> `Token <type-qualifiedretroactiveinterfaceinstance-token-43978_>`_
+ **Method splitImpl \:** `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_ \-\> `Update <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072>`_ (`ContractId <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282>`_ `Token <type-qualifiedretroactiveinterfaceinstance-token-43978_>`_, `ContractId <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282>`_ `Token <type-qualifiedretroactiveinterfaceinstance-token-43978_>`_)
+ **Method transferImpl \:** `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_ \-\> `Update <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072>`_ (`ContractId <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282>`_ `Token <type-qualifiedretroactiveinterfaceinstance-token-43978_>`_)
+ **interface instance** `Token <type-qualifiedretroactiveinterfaceinstance-token-43978_>`_ **for** Asset
@ -84,27 +84,27 @@ Data Types
**data** `TokenView <type-qualifiedretroactiveinterfaceinstance-tokenview-25557_>`_
.. _constr-qualifiedretroactiveinterfaceinstance-tokenview-72346:
`TokenView <constr-qualifiedretroactiveinterfaceinstance-tokenview-72346_>`_
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - owner
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
* - amount
- `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
-
-
**instance** `HasInterfaceView <https://docs.daml.com/daml/stdlib/Prelude.html#class-da-internal-interface-hasinterfaceview-4492>`_ `Token <type-qualifiedretroactiveinterfaceinstance-token-43978_>`_ `TokenView <type-qualifiedretroactiveinterfaceinstance-tokenview-25557_>`_
**instance** `HasField <https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839>`_ \"amount\" `TokenView <type-qualifiedretroactiveinterfaceinstance-tokenview-25557_>`_ `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
**instance** `HasField <https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839>`_ \"owner\" `TokenView <type-qualifiedretroactiveinterfaceinstance-tokenview-25557_>`_ `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
Functions

View File

@ -5,39 +5,39 @@
<a name="type-retroactiveinterfaceinstance-token-49693"></a>**interface** [Token](#type-retroactiveinterfaceinstance-token-49693)
> **viewtype** [TokenView](#type-retroactiveinterfaceinstance-tokenview-57374)
>
>
> * **Choice GetRich**
>
>
> | Field | Type | Description |
> | :----------------------------------------------------------------------------- | :----------------------------------------------------------------------------- | :---------- |
> | byHowMuch | [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) | |
>
>
> * **Choice Noop**
>
>
> | Field | Type | Description |
> | :------ | :------ | :---------- |
> | nothing | () | |
>
>
> * **Choice Split**
>
>
> An interface choice comment.
>
>
> | Field | Type | Description |
> | :----------------------------------------------------------------------------- | :----------------------------------------------------------------------------- | :---------- |
> | splitAmount | [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) | A choice field comment. |
>
>
> * **Choice Transfer**
>
>
> | Field | Type | Description |
> | :-------------------------------------------------------------------------------------- | :-------------------------------------------------------------------------------------- | :---------- |
> | newOwner | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
>
>
> * **Method noopImpl :** () -\> [Update](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072) ()
>
>
> * **Method setAmount :** [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) -\> [Token](#type-retroactiveinterfaceinstance-token-49693)
>
>
> * **Method splitImpl :** [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) -\> [Update](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072) ([ContractId](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282) [Token](#type-retroactiveinterfaceinstance-token-49693), [ContractId](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282) [Token](#type-retroactiveinterfaceinstance-token-49693))
>
>
> * **Method transferImpl :** [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) -\> [Update](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072) ([ContractId](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282) [Token](#type-retroactiveinterfaceinstance-token-49693))
> * **interface instance** [Token](#type-retroactiveinterfaceinstance-token-49693) **for** Asset
@ -47,16 +47,16 @@
<a name="type-retroactiveinterfaceinstance-tokenview-57374"></a>**data** [TokenView](#type-retroactiveinterfaceinstance-tokenview-57374)
> <a name="constr-retroactiveinterfaceinstance-tokenview-95763"></a>[TokenView](#constr-retroactiveinterfaceinstance-tokenview-95763)
>
>
> > | Field | Type | Description |
> > | :-------------------------------------------------------------------------------------- | :-------------------------------------------------------------------------------------- | :---------- |
> > | owner | [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932) | |
> > | amount | [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261) | |
>
>
> **instance** [HasInterfaceView](https://docs.daml.com/daml/stdlib/Prelude.html#class-da-internal-interface-hasinterfaceview-4492) [Token](#type-retroactiveinterfaceinstance-token-49693) [TokenView](#type-retroactiveinterfaceinstance-tokenview-57374)
>
>
> **instance** [HasField](https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839) "amount" [TokenView](#type-retroactiveinterfaceinstance-tokenview-57374) [Int](https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261)
>
>
> **instance** [HasField](https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839) "owner" [TokenView](#type-retroactiveinterfaceinstance-tokenview-57374) [Party](https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932)
## Functions

View File

@ -11,67 +11,67 @@ Interfaces
**interface** `Token <type-retroactiveinterfaceinstance-token-49693_>`_
**viewtype** `TokenView <type-retroactiveinterfaceinstance-tokenview-57374_>`_
+ **Choice GetRich**
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - byHowMuch
- `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
-
-
+ **Choice Noop**
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - nothing
- ()
-
-
+ **Choice Split**
An interface choice comment\.
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - splitAmount
- `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
- A choice field comment\.
+ **Choice Transfer**
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - newOwner
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
+ **Method noopImpl \:** () \-\> `Update <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072>`_ ()
+ **Method setAmount \:** `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_ \-\> `Token <type-retroactiveinterfaceinstance-token-49693_>`_
+ **Method splitImpl \:** `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_ \-\> `Update <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072>`_ (`ContractId <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282>`_ `Token <type-retroactiveinterfaceinstance-token-49693_>`_, `ContractId <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282>`_ `Token <type-retroactiveinterfaceinstance-token-49693_>`_)
+ **Method transferImpl \:** `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_ \-\> `Update <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-update-68072>`_ (`ContractId <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-contractid-95282>`_ `Token <type-retroactiveinterfaceinstance-token-49693_>`_)
+ **interface instance** `Token <type-retroactiveinterfaceinstance-token-49693_>`_ **for** Asset
@ -84,27 +84,27 @@ Data Types
**data** `TokenView <type-retroactiveinterfaceinstance-tokenview-57374_>`_
.. _constr-retroactiveinterfaceinstance-tokenview-95763:
`TokenView <constr-retroactiveinterfaceinstance-tokenview-95763_>`_
.. list-table::
:widths: 15 10 30
:header-rows: 1
* - Field
- Type
- Description
* - owner
- `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
-
-
* - amount
- `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
-
-
**instance** `HasInterfaceView <https://docs.daml.com/daml/stdlib/Prelude.html#class-da-internal-interface-hasinterfaceview-4492>`_ `Token <type-retroactiveinterfaceinstance-token-49693_>`_ `TokenView <type-retroactiveinterfaceinstance-tokenview-57374_>`_
**instance** `HasField <https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839>`_ \"amount\" `TokenView <type-retroactiveinterfaceinstance-tokenview-57374_>`_ `Int <https://docs.daml.com/daml/stdlib/Prelude.html#type-ghc-types-int-37261>`_
**instance** `HasField <https://docs.daml.com/daml/stdlib/DA-Record.html#class-da-internal-record-hasfield-52839>`_ \"owner\" `TokenView <type-retroactiveinterfaceinstance-tokenview-57374_>`_ `Party <https://docs.daml.com/daml/stdlib/Prelude.html#type-da-internal-lf-party-57932>`_
Functions

View File

@ -11,12 +11,12 @@ Data Types
**data** `Color <type-singleconenum-color-64951_>`_
.. _constr-singleconenum-red-9210:
`Red <constr-singleconenum-red-9210_>`_
**instance** `Eq <https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-classes-eq-22713>`_ `Color <type-singleconenum-color-64951_>`_
**instance** `Show <https://docs.daml.com/daml/stdlib/Prelude.html#class-ghc-show-show-65360>`_ `Color <type-singleconenum-color-64951_>`_
Functions