Skip to content

Commit

Permalink
OTP-8308 Added an xsl transform from OTP xml documentation to a file
Browse files Browse the repository at this point in the history
          (.eix) of erlang terms that can be read by the erldoc
          application. Erldoc handles the documentation search mechanism at
          erlang.org. Added generation of eix files to
          otp_release_targets.mk. Fixed a copyright date error in
          db_html.xsl .
  • Loading branch information
lthor authored and Erlang/OTP committed Dec 15, 2009
1 parent 53c1f77 commit f48453e
Show file tree
Hide file tree
Showing 4 changed files with 248 additions and 24 deletions.
206 changes: 206 additions & 0 deletions lib/erl_docgen/priv/xsl/db_eix.xsl
Original file line number Diff line number Diff line change
@@ -0,0 +1,206 @@
<?xml version="1.0" encoding="utf-8"?>
<!--
#
# %CopyrightBegin%
#
# Copyright Ericsson AB 2009. All Rights Reserved.
#
# The contents of this file are subject to the Erlang Public License,
# Version 1.1, (the "License"); you may not use this file except in
# compliance with the License. You should have received a copy of the
# Erlang Public License along with this software. If not, it can be
# retrieved online at http://www.erlang.org/.
#
# Software distributed under the License is distributed on an "AS IS"
# basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
# the License for the specific language governing rights and limitations
# under the License.
#
# %CopyrightEnd%
-->

<xsl:stylesheet version="1.0"
xmlns:xsl="http://www.w3.org/1999/XSL/Transform"
xmlns:fn="http://www.w3.org/2005/02/xpath-functions">

<xsl:output method="text" encoding="UTF-8" indent="no"/>

<!-- Book -->
<xsl:template match="/book">
<xsl:text>%% &#10;%% Search data file for </xsl:text><xsl:value-of select="$appname"/><xsl:text> </xsl:text><xsl:value-of select="$appver"/>
<xsl:text>&#10;%% generated </xsl:text><xsl:value-of select="$gendate"/><xsl:text>&#10;%% &#10;</xsl:text>
<xsl:apply-templates select="applications"/>
<xsl:text>{notused, application, ["</xsl:text><xsl:value-of select="$appname"/><xsl:text>"]}.&#10;</xsl:text>
</xsl:template>

<!-- Applications -->
<xsl:template match="applications">
<xsl:apply-templates name="application"/>
</xsl:template>

<!-- Reference Manual -->

<!-- Application -->
<xsl:template match="application">
<xsl:apply-templates select="erlref|cref|comref|fileref|appref"/>
</xsl:template>

<!-- Erlref -->
<xsl:template match="erlref">
<xsl:text>{"</xsl:text><xsl:value-of select="module"/><xsl:text>.html", {function, {"</xsl:text><xsl:value-of select="$appname"/>
<xsl:text>", "</xsl:text><xsl:value-of select="module"/><xsl:text>"}},&#10;[&#10;</xsl:text>
<xsl:apply-templates select="funcs">
<xsl:with-param name="mod" select="module"/>
</xsl:apply-templates>
<xsl:text>]}.&#10;</xsl:text>
<xsl:text>{"</xsl:text><xsl:value-of select="module"/><xsl:text>.html", {module, "</xsl:text>
<xsl:value-of select="$appname"/><xsl:text>"}, ["</xsl:text><xsl:value-of select="module"/><xsl:text>"]}.&#10;</xsl:text>
</xsl:template>

<!-- Cref -->
<xsl:template match="cref">
<xsl:text>{"</xsl:text><xsl:value-of select="lib"/><xsl:text>.html", {function, {"</xsl:text><xsl:value-of select="$appname"/>
<xsl:text>", "</xsl:text><xsl:value-of select="lib"/><xsl:text>"}}, [&#10;</xsl:text>
<xsl:apply-templates select="funcs">
<xsl:with-param name="mod" select="lib"/>
</xsl:apply-templates>
<xsl:text>]}.&#10;</xsl:text>
<xsl:text>{"</xsl:text><xsl:value-of select="lib"/><xsl:text>.html", {clib, "</xsl:text>
<xsl:value-of select="$appname"/><xsl:text>"}, ["</xsl:text><xsl:value-of select="lib"/><xsl:text>"]}.&#10;</xsl:text>
</xsl:template>

<!-- Comref -->
<xsl:template match="comref">
<xsl:text>{"</xsl:text><xsl:value-of select="com"/><xsl:text>.html", {command, "</xsl:text>
<xsl:value-of select="$appname"/><xsl:text>"}, ["</xsl:text><xsl:value-of select="com"/><xsl:text>"]}.&#10;</xsl:text>
</xsl:template>

<!-- Fileref -->
<xsl:template match="fileref">
<xsl:text>{"</xsl:text><xsl:value-of select="file"/><xsl:text>.html", {file, "</xsl:text>
<xsl:value-of select="$appname"/><xsl:text>"}, ["</xsl:text><xsl:value-of select="file"/><xsl:text>"]}.&#10;</xsl:text>
</xsl:template>

<!-- Appref -->
<xsl:template match="appref">
<xsl:text>{"</xsl:text><xsl:value-of select="app"/><xsl:text>_app.html", {app, "</xsl:text>
<xsl:value-of select="$appname"/><xsl:text>"}, ["</xsl:text><xsl:value-of select="app"/><xsl:text>"]}.&#10;</xsl:text>
</xsl:template>


<!-- Funcs -->
<xsl:template match="funcs">
<xsl:param name="mod"/>
<xsl:variable name="lastfuncsblock">
<xsl:value-of select="position() = last()"/>
</xsl:variable>
<xsl:apply-templates select="func/name">
<xsl:with-param name="mod" select="$mod"/>
<xsl:with-param name="lastfuncsblock" select="$lastfuncsblock"/>
</xsl:apply-templates>
</xsl:template>




<xsl:template match="name">
<xsl:param name="mod"/>
<xsl:param name="lastfuncsblock"/>

<xsl:variable name="tmpstring">
<xsl:value-of select="substring-before(substring-after(., '('), '->')"/>
</xsl:variable>
<xsl:variable name="ustring">
<xsl:choose>
<xsl:when test="string-length($tmpstring) > 0">
<xsl:call-template name="remove-paren">
<xsl:with-param name="string" select="$tmpstring"/>
</xsl:call-template>
</xsl:when>
<xsl:otherwise>
<xsl:call-template name="remove-paren">
<xsl:with-param name="string" select="substring-after(., '(')"/>
</xsl:call-template>
</xsl:otherwise>
</xsl:choose>
</xsl:variable>
<xsl:variable name="arity">
<xsl:call-template name="calc-arity">
<xsl:with-param name="string" select="substring-before($ustring, ')')"/>
<xsl:with-param name="no-of-pars" select="0"/>
</xsl:call-template>
</xsl:variable>
<xsl:variable name="fname">
<xsl:choose>
<xsl:when test="ancestor::cref">
<xsl:value-of select="substring-before(nametext, '(')"/>
</xsl:when>
<xsl:when test="ancestor::erlref">
<xsl:value-of select="substring-before(., '(')"/>
</xsl:when>
</xsl:choose>
</xsl:variable>
<xsl:text> {"</xsl:text><xsl:value-of select="$fname"/>
<xsl:text>", "</xsl:text><xsl:value-of select="$fname"/>
<xsl:text>(</xsl:text><xsl:value-of select="normalize-space($tmpstring)"/>
<xsl:text>", "</xsl:text><xsl:value-of select="$fname"/>
<xsl:text>-</xsl:text><xsl:value-of select="$arity"/><xsl:text>"}</xsl:text>

<xsl:choose>
<xsl:when test="($lastfuncsblock = 'true') and (position() = last())">
<xsl:text>&#10;</xsl:text>
</xsl:when>
<xsl:otherwise>
<xsl:text>,&#10;</xsl:text>
</xsl:otherwise>
</xsl:choose>
</xsl:template>

<!-- Special templates to calculate the arity of functions -->
<xsl:template name="calc-arity">
<xsl:param name="string"/>
<xsl:param name="no-of-pars"/>
<xsl:variable name="length">
<xsl:value-of select="string-length($string)"/>
</xsl:variable>
<xsl:choose>
<xsl:when test="$length > 0">
<xsl:call-template name="calc-arity">
<xsl:with-param name="string" select="substring-after($string, ',')"/>
<xsl:with-param name="no-of-pars" select="$no-of-pars+1"/>
</xsl:call-template>
</xsl:when>
<xsl:otherwise>
<xsl:value-of select="$no-of-pars"/>
</xsl:otherwise>
</xsl:choose>
</xsl:template>

<xsl:template name="remove-paren">
<xsl:param name="string"/>
<xsl:variable name="bstring">
<xsl:value-of select="substring-before($string, '(')"/>
</xsl:variable>
<xsl:choose>
<xsl:when test="string-length($bstring) > 0">
<xsl:variable name="astring">
<xsl:value-of select="substring-after($string, ')')"/>
</xsl:variable>
<xsl:variable name="retstring">
<xsl:call-template name="remove-paren">
<xsl:with-param name="string" select="$astring"/>
</xsl:call-template>
</xsl:variable>
<xsl:value-of select="concat($bstring, $retstring)"/>
</xsl:when>
<xsl:otherwise>
<xsl:value-of select="$string"/>
</xsl:otherwise>
</xsl:choose>
</xsl:template>

<!-- default content handling -->
<xsl:template match="text()"/>

</xsl:stylesheet>
2 changes: 1 addition & 1 deletion lib/erl_docgen/priv/xsl/db_html.xsl
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@
<xsl:value-of select="$copyright"/>
<xsl:value-of select="/book/header/copyright/year[1]"/>
<xsl:text>-</xsl:text>
<xsl:value-of select="substring-after(substring-after($gendate, ' '), ' ')"/>
<xsl:value-of select="substring-after(normalize-space(substring-after($gendate, ' ')), ' ')"/>
<xsl:text> </xsl:text>
<xsl:value-of select="/book/header/copyright/holder"/>
</p>
Expand Down
44 changes: 31 additions & 13 deletions make/otp_release_targets.mk
Original file line number Diff line number Diff line change
@@ -1,24 +1,21 @@
# ``The contents of this file are subject to the Erlang Public License,
#
# %CopyrightBegin%
#
# Copyright Ericsson AB 1997-2009. All Rights Reserved.
#
# The contents of this file are subject to the Erlang Public License,
# Version 1.1, (the "License"); you may not use this file except in
# compliance with the License. You should have received a copy of the
# Erlang Public License along with this software. If not, it can be
# retrieved via the world wide web at http://www.erlang.org/.
# retrieved online at http://www.erlang.org/.
#
# Software distributed under the License is distributed on an "AS IS"
# basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
# the License for the specific language governing rights and limitations
# under the License.
#
# The Initial Developer of the Original Code is Ericsson Utvecklings AB.
# Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
# AB. All Rights Reserved.''
#
# $Id$

# ----------------------------------------------------
# Target for building only the files needed by the Book generation
# ----------------------------------------------------
#texmake: $(TEX_FILES) $(PSFIG_FILES)
# %CopyrightEnd%
#

# ----------------------------------------------------
# Targets for the new documentation support
Expand Down Expand Up @@ -48,6 +45,26 @@ $(HTMLDIR)/users_guide.html: $(XML_FILES)
-path $(DOCGEN)/priv/docbuilder_dtd -path $(DOCGEN)/priv/dtd_html_entities $(DOCGEN)/priv/xsl/db_pdf.xsl book.xml > $@



# ------------------------------------------------------------------------
# The following targets just exist in the documentation directory
# ------------------------------------------------------------------------
ifneq ($(XML_FILES),)

# ----------------------------------------------------
# Generation of application index data
# ----------------------------------------------------
$(HTMLDIR)/$(APPLICATION).eix: $(XML_FILES)
date=`date +"%B %e %Y"`; \
$(XSLTPROC) --stringparam docgen "$(DOCGEN)" \
--stringparam gendate "$$date" --stringparam appname "$(APPLICATION)" --stringparam appver "$(VSN)" --xinclude \
-path $(DOCGEN)/priv/docbuilder_dtd -path $(DOCGEN)/priv/dtd_html_entities $(DOCGEN)/priv/xsl/db_eix.xsl book.xml > $@

docs: $(HTMLDIR)/$(APPLICATION).eix

# ----------------------------------------------------
# Local documentation target for testing
# ----------------------------------------------------
local_docs: TOPDOCDIR=.
local_docs: docs
$(INSTALL) $(DOCGEN)/priv/css/otp_doc.css $(HTMLDIR)
Expand All @@ -59,6 +76,7 @@ local_docs: docs
$(DOCGEN)/priv/js/flipmenu/flip_static.gif \
$(DOCGEN)/priv/js/flipmenu/flipmenu.js $(HTMLDIR)/js/flipmenu

endif

# ----------------------------------------------------
# Standard release target
Expand All @@ -73,6 +91,6 @@ release release_docs release_tests release_html:
else

release release_docs release_tests release_html:
$(MAKE) $(MFLAGS) RELEASE_PATH=$(TESTROOT) $(TARGET_MAKEFILE) $@_spec
$(MAKE) $(MFLAGS) RELEASE_PATH=$(TESTROOT) $(TARGET_MAKEFILE) $@_spec

endif
20 changes: 10 additions & 10 deletions make/otp_subdir.mk
Original file line number Diff line number Diff line change
@@ -1,30 +1,30 @@
# ``The contents of this file are subject to the Erlang Public License,
#
# %CopyrightBegin%
#
# Copyright Ericsson AB 1997-2009. All Rights Reserved.
#
# The contents of this file are subject to the Erlang Public License,
# Version 1.1, (the "License"); you may not use this file except in
# compliance with the License. You should have received a copy of the
# Erlang Public License along with this software. If not, it can be
# retrieved via the world wide web at http://www.erlang.org/.
# retrieved online at http://www.erlang.org/.
#
# Software distributed under the License is distributed on an "AS IS"
# basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
# the License for the specific language governing rights and limitations
# under the License.
#
# The Initial Developer of the Original Code is Ericsson Utvecklings AB.
# Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
# AB. All Rights Reserved.''
#
# $Id$
#
# %CopyrightEnd%
#
# Make include file for otp

.PHONY: debug opt release local_docs docs release_docs tests release_tests \
.PHONY: debug opt release docs release_docs tests release_tests \
clean depend valgrind

#
# Targets that don't affect documentation directories
#
opt debug release local_docs docs release_docs tests release_tests clean depend valgrind:
opt debug release docs release_docs tests release_tests clean depend valgrind:
@set -e ; \
app_pwd=`pwd` ; \
if test -f vsn.mk; then \
Expand Down

0 comments on commit f48453e

Please sign in to comment.