daml-docs: Generate Hoogle database with anchor table from generating docs. (#5704)

* Fix all DAML hoogle links.

This PR changes how the hoogle database is rendered in damldocs, so it has access to the mapping of anchors to URLs that is produced during rendering of rst docs. This way these will not get out of sync.

I also added an --output-anchor option in preparation for fixing external/cross-package references.

changelog_begin
changelog_end

* Update settings.json

undo accidental vscode settings change.

* Update README.md
This commit is contained in:
Sofia Faro 2020-04-23 16:12:48 +01:00 committed by GitHub
parent 15354c3256
commit 6047cca194
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
12 changed files with 193 additions and 95 deletions

View File

@ -249,36 +249,15 @@ genrule(
) )
genrule( genrule(
name = "daml-base-hoogle-docs", name = "daml-base-docs",
srcs = [ srcs = [
":daml-prim.json", ":daml-prim.json",
":daml-stdlib.json", ":daml-stdlib.json",
":daml-base-hoogle-template", ":daml-base-hoogle-template",
],
outs = ["daml-base-hoogle.txt"],
cmd = """
$(location //compiler/damlc) -- docs \
--output=$(OUTS) \
--input-format=json \
--format=Hoogle \
--exclude-instances=HasField \
--drop-orphan-instances \
--template=$(location :daml-base-hoogle-template) \
$(location :daml-stdlib.json) $(location :daml-prim.json)
""",
tools = ["//compiler/damlc"],
visibility = ["//visibility:public"],
)
genrule(
name = "daml-base-rst-docs",
srcs = [
":daml-prim.json",
":daml-stdlib.json",
":daml-base-rst-index-template", ":daml-base-rst-index-template",
":daml-base-rst-template", ":daml-base-rst-template",
], ],
outs = ["daml-base-rst.tar.gz"], outs = ["daml-base-rst.tar.gz", "daml-base-hoogle.txt"],
cmd = """ cmd = """
$(location //compiler/damlc) -- docs \ $(location //compiler/damlc) -- docs \
--output=daml-base-rst \ --output=daml-base-rst \
@ -288,10 +267,13 @@ genrule(
--drop-orphan-instances \ --drop-orphan-instances \
--template=$(location :daml-base-rst-template) \ --template=$(location :daml-base-rst-template) \
--index-template=$(location :daml-base-rst-index-template) \ --index-template=$(location :daml-base-rst-index-template) \
--hoogle-template=$(location :daml-base-hoogle-template) \
--base-url=https://docs.daml.com/daml/stdlib \
--output-hoogle=$(location :daml-base-hoogle.txt) \
$(location :daml-stdlib.json) $(location :daml-prim.json) $(location :daml-stdlib.json) $(location :daml-prim.json)
tar c daml-base-rst \ tar c daml-base-rst \
--owner=0 --group=0 --numeric-owner --mtime=2000-01-01\ 00:00Z --sort=name \ --owner=0 --group=0 --numeric-owner --mtime=2000-01-01\ 00:00Z --sort=name \
| gzip -n > $(OUTS) | gzip -n > $(location :daml-base-rst.tar.gz)
""", """,
tools = ["//compiler/damlc"], tools = ["//compiler/damlc"],
visibility = ["//visibility:public"], visibility = ["//visibility:public"],

View File

@ -96,10 +96,11 @@ to accept the current documentation as new golden files.
Standard library docs are exposed under the bazel rules which you can build with: Standard library docs are exposed under the bazel rules which you can build with:
``` ```
bazel build //compiler/damlc:daml-base-rst-docs bazel build //compiler/damlc:daml-base-docs
bazel build //compiler/damlc:daml-base-hoogle-docs
``` ```
This creates a tarball containing RST (ReStructured Text) docs, and a hoogle database.
## DAML Packages and Database ## DAML Packages and Database
A DAML project is compiled to a DAML package and can be distributed as a DAML archive (DAR). This is A DAML project is compiled to a DAML package and can be distributed as a DAML archive (DAR). This is

View File

@ -5,6 +5,8 @@
-- All rights reserved. Any unauthorized use, duplication or distribution is strictly prohibited. -- All rights reserved. Any unauthorized use, duplication or distribution is strictly prohibited.
-- | DAML standard library. -- | DAML standard library.
@url https://docs.daml.com/daml/stdlib/index.html @url {{base-url}}
@package base @package daml-stdlib
@version 1.2.0 @version 1.2.0
{{{body}}}

View File

@ -44,17 +44,21 @@ data DamldocOptions = DamldocOptions
, do_outputFormat :: OutputFormat , do_outputFormat :: OutputFormat
, do_docTemplate :: Maybe FilePath , do_docTemplate :: Maybe FilePath
, do_docIndexTemplate :: Maybe FilePath , do_docIndexTemplate :: Maybe FilePath
, do_docHoogleTemplate :: Maybe FilePath
, do_transformOptions :: TransformOptions , do_transformOptions :: TransformOptions
, do_inputFiles :: [NormalizedFilePath] , do_inputFiles :: [NormalizedFilePath]
, do_docTitle :: Maybe T.Text , do_docTitle :: Maybe T.Text
, do_combine :: Bool , do_combine :: Bool
, do_extractOptions :: ExtractOptions , do_extractOptions :: ExtractOptions
, do_baseURL :: Maybe T.Text -- ^ base URL for generated documentation
, do_hooglePath :: Maybe FilePath -- ^ hoogle database output path
, do_anchorPath :: Maybe FilePath -- ^ anchor table output path
} }
data InputFormat = InputJson | InputDaml data InputFormat = InputJson | InputDaml
deriving (Eq, Show, Read) deriving (Eq, Show, Read)
data OutputFormat = OutputJson | OutputHoogle | OutputDocs RenderFormat data OutputFormat = OutputJson | OutputDocs RenderFormat
deriving (Eq, Show, Read) deriving (Eq, Show, Read)
-- | Run damldocs! -- | Run damldocs!
@ -92,6 +96,7 @@ renderDocData :: DamldocOptions -> [ModuleDoc] -> IO ()
renderDocData DamldocOptions{..} docData = do renderDocData DamldocOptions{..} docData = do
templateM <- mapM T.readFileUtf8 do_docTemplate templateM <- mapM T.readFileUtf8 do_docTemplate
indexTemplateM <- mapM T.readFileUtf8 do_docIndexTemplate indexTemplateM <- mapM T.readFileUtf8 do_docIndexTemplate
hoogleTemplateM <- mapM T.readFileUtf8 do_docHoogleTemplate
let prefix = fromMaybe "" templateM let prefix = fromMaybe "" templateM
write file contents = do write file contents = do
@ -102,8 +107,6 @@ renderDocData DamldocOptions{..} docData = do
case do_outputFormat of case do_outputFormat of
OutputJson -> OutputJson ->
write do_outputPath $ T.decodeUtf8 . LBS.toStrict $ AP.encodePretty' jsonConf docData write do_outputPath $ T.decodeUtf8 . LBS.toStrict $ AP.encodePretty' jsonConf docData
OutputHoogle ->
write do_outputPath . T.concat $ map renderSimpleHoogle docData
OutputDocs format -> do OutputDocs format -> do
let renderOptions = RenderOptions let renderOptions = RenderOptions
{ ro_mode = { ro_mode =
@ -114,5 +117,9 @@ renderDocData DamldocOptions{..} docData = do
, ro_title = do_docTitle , ro_title = do_docTitle
, ro_template = templateM , ro_template = templateM
, ro_indexTemplate = indexTemplateM , ro_indexTemplate = indexTemplateM
, ro_hoogleTemplate = hoogleTemplateM
, ro_baseURL = do_baseURL
, ro_hooglePath = do_hooglePath
, ro_anchorPath = do_anchorPath
} }
renderDocs renderOptions docData renderDocs renderOptions docData

View File

@ -22,8 +22,8 @@ import DA.Daml.Doc.Render.Hoogle
import DA.Daml.Doc.Render.Output import DA.Daml.Doc.Render.Output
import DA.Daml.Doc.Types import DA.Daml.Doc.Types
import Control.Monad.Extra
import Data.Maybe import Data.Maybe
import Data.List.Extra
import Data.Foldable import Data.Foldable
import System.Directory import System.Directory
import System.FilePath import System.FilePath
@ -31,7 +31,7 @@ import System.IO
import System.Exit import System.Exit
import qualified CMarkGFM as GFM import qualified CMarkGFM as GFM
import qualified Data.Aeson.Types as A import qualified Data.Aeson as A
import qualified Data.Aeson.Encode.Pretty as AP import qualified Data.Aeson.Encode.Pretty as AP
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy as TL
@ -45,13 +45,14 @@ jsonConf :: AP.Config
jsonConf = AP.Config (AP.Spaces 2) (AP.keyOrder ["id"]) AP.Generic True jsonConf = AP.Config (AP.Spaces 2) (AP.keyOrder ["id"]) AP.Generic True
renderDocs :: RenderOptions -> [ModuleDoc] -> IO () renderDocs :: RenderOptions -> [ModuleDoc] -> IO ()
renderDocs RenderOptions{..} mods = do renderDocs ro@RenderOptions{..} mods = do
let (formatter, postProcessing) = let (formatter, postProcessing) =
case ro_format of case ro_format of
Rst -> (renderRst, id) Rst -> (renderRst, id)
Markdown -> (renderMd, id) Markdown -> (renderMd, id)
Html -> (renderMd, GFM.commonmarkToHtml [GFM.optUnsafe] [GFM.extTable]) Html -> (renderMd, GFM.commonmarkToHtml [GFM.optUnsafe] [GFM.extTable])
templateText = fromMaybe (defaultTemplate ro_format) ro_template templateText = fromMaybe (defaultTemplate ro_format) ro_template
renderMap = Map.fromList [(md_name mod, renderModule mod) | mod <- mods]
template <- compileTemplate "template" templateText template <- compileTemplate "template" templateText
@ -59,15 +60,13 @@ renderDocs RenderOptions{..} mods = do
RenderToFile path -> do RenderToFile path -> do
BS.writeFile path BS.writeFile path
. T.encodeUtf8 . T.encodeUtf8
. renderTemplate template . renderTemplate ro template
(fromMaybe "Package Docs" ro_title)
. postProcessing . postProcessing
. renderPage formatter . renderPage formatter
$ mconcatMap renderModule mods $ fold renderMap
RenderToFolder path -> do RenderToFolder path -> do
let renderMap = Map.fromList let
[(md_name mod, renderModule mod) | mod <- mods]
(outputIndex, outputMap) = renderFolder formatter renderMap (outputIndex, outputMap) = renderFolder formatter renderMap
extension = extension =
case ro_format of case ro_format of
@ -76,16 +75,12 @@ renderDocs RenderOptions{..} mods = do
Html -> "html" Html -> "html"
outputPath mod = path </> moduleNameToFileName mod <.> extension outputPath mod = path </> moduleNameToFileName mod <.> extension
pageTitle mod = T.concat
[ maybe "" (<> " - ") ro_title
, "Module "
, unModulename mod ]
createDirectoryIfMissing True path createDirectoryIfMissing True path
for_ (Map.toList outputMap) $ \ (mod, renderedOutput) -> do for_ (Map.toList outputMap) $ \ (mod, renderedOutput) -> do
BS.writeFile (outputPath mod) BS.writeFile (outputPath mod)
. T.encodeUtf8 . T.encodeUtf8
. renderTemplate template (pageTitle mod) . renderTemplate ro template
. postProcessing . postProcessing
$ renderedOutput $ renderedOutput
@ -94,10 +89,23 @@ renderDocs RenderOptions{..} mods = do
BS.writeFile (path </> "index" <.> extension) BS.writeFile (path </> "index" <.> extension)
. T.encodeUtf8 . T.encodeUtf8
. renderTemplate indexTemplate (fromMaybe "index" ro_title) . renderTemplate ro indexTemplate
. postProcessing . postProcessing
$ outputIndex $ outputIndex
let anchorTable = buildAnchorTable ro renderMap
whenJust ro_anchorPath $ \anchorPath -> do
A.encodeFile anchorPath anchorTable
whenJust ro_hooglePath $ \hooglePath -> do
let he = HoogleEnv { he_anchorTable = anchorTable }
hoogleTemplate <- compileTemplate "hoogle template"
(fromMaybe defaultHoogleTemplate ro_hoogleTemplate)
BS.writeFile hooglePath
. T.encodeUtf8
. renderTemplate ro hoogleTemplate
. T.concat
$ map (renderSimpleHoogle he) mods
compileTemplate :: T.Text -> T.Text -> IO M.Template compileTemplate :: T.Text -> T.Text -> IO M.Template
compileTemplate templateName templateText = compileTemplate templateName templateText =
case M.compileMustacheText "daml docs template" templateText of case M.compileMustacheText "daml docs template" templateText of
@ -107,16 +115,29 @@ compileTemplate templateName templateText =
exitFailure exitFailure
renderTemplate :: renderTemplate ::
M.Template -- ^ template RenderOptions
-> T.Text -- ^ page title -> M.Template -- ^ template
-> T.Text -- ^ page body -> T.Text -- ^ page body
-> T.Text -> T.Text
renderTemplate template pageTitle pageBody = renderTemplate RenderOptions{..} template pageBody =
TL.toStrict . M.renderMustache template . A.object $ TL.toStrict . M.renderMustache template . A.object $
[ "title" A..= pageTitle [ "base-url" A..= fromMaybe "" ro_baseURL
, "title" A..= fromMaybe "" ro_title
, "body" A..= pageBody , "body" A..= pageBody
] ]
defaultHoogleTemplate :: T.Text
defaultHoogleTemplate = T.unlines
[ "-- Hoogle database generated by damlc."
, "-- See Hoogle, http://www.haskell.org/hoogle/"
, ""
, "@url {{{base-url}}}"
, "@package {{package-name}}" -- TODO
, "@version {{package-version}}" -- TODO
, ""
, "{{{body}}}"
]
defaultTemplate :: RenderFormat -> T.Text defaultTemplate :: RenderFormat -> T.Text
defaultTemplate = \case defaultTemplate = \case
Html -> defaultTemplateHtml Html -> defaultTemplateHtml

View File

@ -3,15 +3,21 @@
module DA.Daml.Doc.Render.Hoogle module DA.Daml.Doc.Render.Hoogle
( renderSimpleHoogle ( HoogleEnv (..)
) where , renderSimpleHoogle
) where
import DA.Daml.Doc.Types import DA.Daml.Doc.Types
import DA.Daml.Doc.Render.Util import DA.Daml.Doc.Render.Util
import Data.Maybe import Data.Maybe
import qualified Data.HashMap.Strict as HMS
import qualified Data.Text as T import qualified Data.Text as T
newtype HoogleEnv = HoogleEnv
{ he_anchorTable :: HMS.HashMap Anchor T.Text
}
-- | Convert a markdown comment into hoogle text. -- | Convert a markdown comment into hoogle text.
hooglify :: Maybe DocText -> [T.Text] hooglify :: Maybe DocText -> [T.Text]
hooglify Nothing = [] hooglify Nothing = []
@ -21,46 +27,46 @@ hooglify (Just md) =
(x:xs) -> ("-- | " <> x) (x:xs) -> ("-- | " <> x)
: map ("-- " <>) xs : map ("-- " <>) xs
urlTag :: Maybe Anchor -> T.Text urlTag :: HoogleEnv -> Maybe Anchor -> T.Text
urlTag Nothing = "" urlTag env anchorM = fromMaybe "" $ do
urlTag (Just (Anchor t)) = "@url https://docs.daml.com/daml/stdlib/index.html#" <> t anchor <- anchorM
-- ^ TODO(sofia): This needs a map of anchors to final module names / filenames. url <- HMS.lookup anchor (he_anchorTable env)
-- Or maybe there is a sphinx setting/plugin to create anchor-based redirects for us... pure ("@url " <> url)
renderSimpleHoogle :: ModuleDoc -> T.Text renderSimpleHoogle :: HoogleEnv -> ModuleDoc -> T.Text
renderSimpleHoogle ModuleDoc{..} renderSimpleHoogle _env ModuleDoc{..}
| null md_classes && null md_adts && | null md_classes && null md_adts &&
null md_functions && isNothing md_descr = T.empty null md_functions && isNothing md_descr = T.empty
renderSimpleHoogle ModuleDoc{..} = T.unlines . concat $ renderSimpleHoogle env ModuleDoc{..} = T.unlines . concat $
[ hooglify md_descr [ hooglify md_descr
, [ urlTag md_anchor , [ urlTag env md_anchor
, "module " <> unModulename md_name , "module " <> unModulename md_name
, "" ] , "" ]
, concatMap adt2hoogle md_adts , concatMap (adt2hoogle env) md_adts
, concatMap cls2hoogle md_classes , concatMap (cls2hoogle env) md_classes
, concatMap fct2hoogle md_functions , concatMap (fct2hoogle env) md_functions
] ]
adt2hoogle :: ADTDoc -> [T.Text] adt2hoogle :: HoogleEnv -> ADTDoc -> [T.Text]
adt2hoogle TypeSynDoc{..} = concat adt2hoogle env TypeSynDoc{..} = concat
[ hooglify ad_descr [ hooglify ad_descr
, [ urlTag ad_anchor , [ urlTag env ad_anchor
, T.unwords ("type" : wrapOp (unTypename ad_name) : , T.unwords ("type" : wrapOp (unTypename ad_name) :
ad_args ++ ["=", type2hoogle ad_rhs]) ad_args ++ ["=", type2hoogle ad_rhs])
, "" ] , "" ]
] ]
adt2hoogle ADTDoc{..} = concat adt2hoogle env ADTDoc{..} = concat
[ hooglify ad_descr [ hooglify ad_descr
, [ urlTag ad_anchor , [ urlTag env ad_anchor
, T.unwords ("data" : wrapOp (unTypename ad_name) : ad_args) , T.unwords ("data" : wrapOp (unTypename ad_name) : ad_args)
, "" ] , "" ]
, concatMap (adtConstr2hoogle ad_name) ad_constrs , concatMap (adtConstr2hoogle env ad_name) ad_constrs
] ]
adtConstr2hoogle :: Typename -> ADTConstr -> [T.Text] adtConstr2hoogle :: HoogleEnv -> Typename -> ADTConstr -> [T.Text]
adtConstr2hoogle typename PrefixC{..} = concat adtConstr2hoogle env typename PrefixC{..} = concat
[ hooglify ac_descr [ hooglify ac_descr
, [ urlTag ac_anchor , [ urlTag env ac_anchor
, T.unwords , T.unwords
[ wrapOp (unTypename ac_name) [ wrapOp (unTypename ac_name)
, "::" , "::"
@ -68,9 +74,9 @@ adtConstr2hoogle typename PrefixC{..} = concat
] ]
, "" ] , "" ]
] ]
adtConstr2hoogle typename RecordC{..} = concat adtConstr2hoogle env typename RecordC{..} = concat
[ hooglify ac_descr [ hooglify ac_descr
, [ urlTag ac_anchor , [ urlTag env ac_anchor
, T.unwords , T.unwords
[ wrapOp (unTypename ac_name) [ wrapOp (unTypename ac_name)
, "::" , "::"
@ -95,22 +101,22 @@ fieldDoc2hoogle typename FieldDoc{..} = concat
] ]
cls2hoogle :: ClassDoc -> [T.Text] cls2hoogle :: HoogleEnv -> ClassDoc -> [T.Text]
cls2hoogle ClassDoc{..} = concat cls2hoogle env ClassDoc{..} = concat
[ hooglify cl_descr [ hooglify cl_descr
, [ urlTag cl_anchor , [ urlTag env cl_anchor
, T.unwords $ ["class"] , T.unwords $ ["class"]
++ maybe [] ((:["=>"]) . type2hoogle) cl_super ++ maybe [] ((:["=>"]) . type2hoogle) cl_super
++ wrapOp (unTypename cl_name) : cl_args ++ wrapOp (unTypename cl_name) : cl_args
, "" ] , "" ]
, concatMap classMethod2hoogle cl_methods , concatMap (classMethod2hoogle env) cl_methods
] ]
classMethod2hoogle :: ClassMethodDoc -> [T.Text] classMethod2hoogle :: HoogleEnv -> ClassMethodDoc -> [T.Text]
classMethod2hoogle ClassMethodDoc{..} | cm_isDefault = [] -- hide default methods from hoogle search classMethod2hoogle _env ClassMethodDoc{..} | cm_isDefault = [] -- hide default methods from hoogle search
classMethod2hoogle ClassMethodDoc{..} = concat classMethod2hoogle env ClassMethodDoc{..} = concat
[ hooglify cm_descr [ hooglify cm_descr
, [ urlTag cm_anchor , [ urlTag env cm_anchor
, T.unwords . concat $ , T.unwords . concat $
[ [wrapOp (unFieldname cm_name), "::"] [ [wrapOp (unFieldname cm_name), "::"]
, maybe [] ((:["=>"]) . type2hoogle) cm_globalContext , maybe [] ((:["=>"]) . type2hoogle) cm_globalContext
@ -119,10 +125,10 @@ classMethod2hoogle ClassMethodDoc{..} = concat
, "" ] , "" ]
] ]
fct2hoogle :: FunctionDoc -> [T.Text] fct2hoogle :: HoogleEnv -> FunctionDoc -> [T.Text]
fct2hoogle FunctionDoc{..} = concat fct2hoogle env FunctionDoc{..} = concat
[ hooglify fct_descr [ hooglify fct_descr
, [ urlTag fct_anchor , [ urlTag env fct_anchor
, T.unwords . concat $ , T.unwords . concat $
[ [wrapOp (unFieldname fct_name), "::"] [ [wrapOp (unFieldname fct_name), "::"]
, maybe [] ((:["=>"]) . type2hoogle) fct_context , maybe [] ((:["=>"]) . type2hoogle) fct_context

View File

@ -9,12 +9,14 @@ module DA.Daml.Doc.Render.Monoid
) where ) where
import DA.Daml.Doc.Types import DA.Daml.Doc.Types
import DA.Daml.Doc.Render.Types
import Control.Monad import Control.Monad
import Data.Foldable import Data.Foldable
import Data.Maybe import Data.Maybe
import Data.List.Extra import Data.List.Extra
import System.FilePath import System.FilePath
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import qualified Data.HashMap.Strict as HMS
import qualified Data.Set as Set import qualified Data.Set as Set
import qualified Data.Text as T import qualified Data.Text as T
import qualified Network.URI as URI import qualified Network.URI as URI
@ -173,3 +175,38 @@ renderFolder formatter fileMap =
moduleNameToFileName :: Modulename -> FilePath moduleNameToFileName :: Modulename -> FilePath
moduleNameToFileName = moduleNameToFileName =
T.unpack . T.replace "." "-" . unModulename T.unpack . T.replace "." "-" . unModulename
buildAnchorTable :: RenderOptions -> Map.Map Modulename RenderOut -> HMS.HashMap Anchor T.Text
buildAnchorTable RenderOptions{..} outputs
| Just baseURL <- ro_baseURL
= HMS.fromList
[ (anchor, buildURL baseURL moduleName anchor)
| (moduleName, output) <- Map.toList outputs
, anchor <- Set.toList (getRenderAnchors output)
]
where
stripTrailingSlash :: T.Text -> T.Text
stripTrailingSlash x = fromMaybe x (T.stripSuffix "/" x)
buildURL :: T.Text -> Modulename -> Anchor -> T.Text
buildURL = case ro_mode of
RenderToFile _ -> buildFileURL
RenderToFolder _ -> buildFolderURL
buildFileURL :: T.Text -> Modulename -> Anchor -> T.Text
buildFileURL baseURL _ anchor = T.concat
[ baseURL
, "#"
, unAnchor anchor
]
buildFolderURL :: T.Text -> Modulename -> Anchor -> T.Text
buildFolderURL baseURL moduleName anchor = T.concat
[ stripTrailingSlash baseURL
, "/"
, T.pack (moduleNameToFileName moduleName <.> "html")
, "#"
, unAnchor anchor
]
buildAnchorTable _ _ = HMS.empty

View File

@ -24,4 +24,8 @@ data RenderOptions = RenderOptions
, ro_title :: Maybe T.Text -- ^ title of rendered documentation , ro_title :: Maybe T.Text -- ^ title of rendered documentation
, ro_template :: Maybe T.Text -- ^ renderer template , ro_template :: Maybe T.Text -- ^ renderer template
, ro_indexTemplate :: Maybe T.Text -- ^ renderer template for index , ro_indexTemplate :: Maybe T.Text -- ^ renderer template for index
, ro_hoogleTemplate :: Maybe T.Text -- ^ renderer template for hoogle database
, ro_baseURL :: Maybe T.Text -- ^ base URL for generated documentation
, ro_hooglePath :: Maybe FilePath -- ^ path to output hoogle database
, ro_anchorPath :: Maybe FilePath -- ^ path to output anchor table
} }

View File

@ -80,7 +80,7 @@ data Reference = Reference
-- | Anchors are URL-safe (and RST-safe!) ids into the docs. -- | Anchors are URL-safe (and RST-safe!) ids into the docs.
newtype Anchor = Anchor { unAnchor :: Text } newtype Anchor = Anchor { unAnchor :: Text }
deriving newtype (Eq, Ord, Show, ToJSON, FromJSON, IsString) deriving newtype (Eq, Ord, Show, ToJSON, ToJSONKey, FromJSON, IsString, Hashable)
------------------------------------------------------------ ------------------------------------------------------------
-- | Documentation data for a module -- | Documentation data for a module

View File

@ -33,6 +33,7 @@ documentation numProcessors = Damldoc
<*> optOutputFormat <*> optOutputFormat
<*> optTemplate <*> optTemplate
<*> optIndexTemplate <*> optIndexTemplate
<*> optHoogleTemplate
<*> optOmitEmpty <*> optOmitEmpty
<*> optDataOnly <*> optDataOnly
<*> optNoAnnot <*> optNoAnnot
@ -42,6 +43,9 @@ documentation numProcessors = Damldoc
<*> optDropOrphanInstances <*> optDropOrphanInstances
<*> optCombine <*> optCombine
<*> optExtractOptions <*> optExtractOptions
<*> optBaseURL
<*> optHooglePath
<*> optAnchorPath
<*> argMainFiles <*> argMainFiles
where where
optInputFormat :: Parser InputFormat optInputFormat :: Parser InputFormat
@ -67,6 +71,27 @@ documentation numProcessors = Damldoc
<> long "output" <> long "output"
<> short 'o' <> short 'o'
optBaseURL :: Parser (Maybe T.Text)
optBaseURL =
optional . fmap T.pack . option str
$ metavar "URL"
<> help "Base URL for generated documentation."
<> long "base-url"
optHooglePath :: Parser (Maybe FilePath)
optHooglePath =
optional . option str
$ metavar "PATH"
<> help "Path to output hoogle database."
<> long "output-hoogle"
optAnchorPath :: Parser (Maybe FilePath)
optAnchorPath =
optional . option str
$ metavar "PATH"
<> help "Path to output anchor table."
<> long "output-anchor"
optTemplate :: Parser (Maybe FilePath) optTemplate :: Parser (Maybe FilePath)
optTemplate = optTemplate =
optional . option str optional . option str
@ -82,6 +107,13 @@ documentation numProcessors = Damldoc
<> help "Path to mustache template for index, when rendering to a folder. The variable 'body' in the template is substituted with a module index." <> help "Path to mustache template for index, when rendering to a folder. The variable 'body' in the template is substituted with a module index."
<> long "index-template" <> long "index-template"
optHoogleTemplate :: Parser (Maybe FilePath)
optHoogleTemplate =
optional . option str
$ metavar "FILE"
<> help "Path to mustache template for hoogle database."
<> long "hoogle-template"
argMainFiles :: Parser [FilePath] argMainFiles :: Parser [FilePath]
argMainFiles = some $ argument str $ metavar "FILE..." argMainFiles = some $ argument str $ metavar "FILE..."
<> help "Main file(s) (*.daml) whose contents are read" <> help "Main file(s) (*.daml) whose contents are read"
@ -102,9 +134,8 @@ documentation numProcessors = Damldoc
"md" -> Right (OutputDocs Markdown) "md" -> Right (OutputDocs Markdown)
"markdown" -> Right (OutputDocs Markdown) "markdown" -> Right (OutputDocs Markdown)
"html" -> Right (OutputDocs Html) "html" -> Right (OutputDocs Html)
"hoogle" -> Right OutputHoogle
"json" -> Right OutputJson "json" -> Right OutputJson
_ -> Left "Unknown output format. Expected rst, md, markdown, html, hoogle, or json." _ -> Left "Unknown output format. Expected rst, md, markdown, html, or json."
optOmitEmpty :: Parser Bool optOmitEmpty :: Parser Bool
optOmitEmpty = switch optOmitEmpty = switch
@ -199,6 +230,7 @@ data CmdArgs = Damldoc
, cOutputFormat :: OutputFormat , cOutputFormat :: OutputFormat
, cTemplate :: Maybe FilePath , cTemplate :: Maybe FilePath
, cIndexTemplate :: Maybe FilePath , cIndexTemplate :: Maybe FilePath
, cHoogleTemplate :: Maybe FilePath
, cOmitEmpty :: Bool , cOmitEmpty :: Bool
, cDataOnly :: Bool , cDataOnly :: Bool
, cNoAnnot :: Bool , cNoAnnot :: Bool
@ -208,6 +240,9 @@ data CmdArgs = Damldoc
, cDropOrphanInstances :: Bool , cDropOrphanInstances :: Bool
, cCombine :: Bool , cCombine :: Bool
, cExtractOptions :: ExtractOptions , cExtractOptions :: ExtractOptions
, cBaseURL :: Maybe T.Text
, cHooglePath :: Maybe FilePath
, cAnchorPath :: Maybe FilePath
, cMainFiles :: [FilePath] , cMainFiles :: [FilePath]
} deriving (Show) } deriving (Show)
@ -227,10 +262,14 @@ exec Damldoc{..} = do
, do_inputFiles = map toNormalizedFilePath' cMainFiles , do_inputFiles = map toNormalizedFilePath' cMainFiles
, do_docTemplate = cTemplate , do_docTemplate = cTemplate
, do_docIndexTemplate = cIndexTemplate , do_docIndexTemplate = cIndexTemplate
, do_docHoogleTemplate = cHoogleTemplate
, do_transformOptions = transformOptions , do_transformOptions = transformOptions
, do_docTitle = T.pack . unitIdString <$> optUnitId cOptions , do_docTitle = T.pack . unitIdString <$> optUnitId cOptions
, do_combine = cCombine , do_combine = cCombine
, do_extractOptions = cExtractOptions , do_extractOptions = cExtractOptions
, do_baseURL = cBaseURL
, do_hooglePath = cHooglePath
, do_anchorPath = cAnchorPath
} }
where where

View File

@ -261,7 +261,7 @@ genrule(
genrule( genrule(
name = "sources", name = "sources",
srcs = glob(["source/**"]) + [ srcs = glob(["source/**"]) + [
"//compiler/damlc:daml-base-rst-docs", "//compiler/damlc:daml-base-rst.tar.gz",
"//triggers/daml:daml-trigger-rst-docs", "//triggers/daml:daml-trigger-rst-docs",
"//daml-script/daml:daml-script-rst-docs", "//daml-script/daml:daml-script-rst-docs",
"//ledger-api/grpc-definitions:docs", "//ledger-api/grpc-definitions:docs",
@ -274,7 +274,7 @@ genrule(
# Copy in Stdlib # Copy in Stdlib
mkdir -p source/daml/stdlib mkdir -p source/daml/stdlib
tar xf $(location //compiler/damlc:daml-base-rst-docs) \ tar xf $(location //compiler/damlc:daml-base-rst.tar.gz) \
--strip-components 1 \ --strip-components 1 \
-C source/daml/stdlib -C source/daml/stdlib
@ -354,8 +354,7 @@ genrule(
]) + [ ]) + [
":sources", ":sources",
":theme", ":theme",
"//compiler/damlc:daml-base-rst-docs", "//compiler/damlc:daml-base-hoogle.txt",
"//compiler/damlc:daml-base-hoogle-docs",
"//language-support/java:javadoc", "//language-support/java:javadoc",
"//language-support/ts/daml-react:docs", "//language-support/ts/daml-react:docs",
"//language-support/ts/daml-ledger:docs", "//language-support/ts/daml-ledger:docs",
@ -417,7 +416,7 @@ genrule(
# Copy in hoogle DB # Copy in hoogle DB
mkdir -p html/hoogle_db mkdir -p html/hoogle_db
cp -rL ../$(location //compiler/damlc:daml-base-hoogle-docs) html/hoogle_db/base.txt cp -rL ../$(location //compiler/damlc:daml-base-hoogle.txt) html/hoogle_db/base.txt
tar c html \ tar c html \
--owner=0 --group=0 --numeric-owner --mtime=2000-01-01\ 00:00Z --sort=name \ --owner=0 --group=0 --numeric-owner --mtime=2000-01-01\ 00:00Z --sort=name \

View File

@ -45,7 +45,7 @@ do
fi fi
if [ "$arg" = "--gen" ]; then if [ "$arg" = "--gen" ]; then
# Hoogle # Hoogle
bazel build //compiler/damlc:daml-base-hoogle-docs bazel build //compiler/damlc:daml-base-hoogle.txt
mkdir -p $BUILD_DIR/gen/hoogle_db mkdir -p $BUILD_DIR/gen/hoogle_db
cp -L ../../bazel-bin/compiler/damlc/daml-base-hoogle.txt $BUILD_DIR/gen/hoogle_db/base.txt cp -L ../../bazel-bin/compiler/damlc/daml-base-hoogle.txt $BUILD_DIR/gen/hoogle_db/base.txt