Skip to content

Commit

Permalink
drop --html-manual option
Browse files Browse the repository at this point in the history
fixes cp2k#518
  • Loading branch information
dev-zero committed Aug 26, 2019
1 parent 426263c commit 2fba3c9
Show file tree
Hide file tree
Showing 4 changed files with 25 additions and 482 deletions.
157 changes: 2 additions & 155 deletions src/input/input_keyword_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -24,9 +24,7 @@ MODULE input_keyword_types
USE kinds, ONLY: default_string_length,&
dp
USE print_messages, ONLY: print_message
USE reference_manager, ONLY: get_citation_key,&
print_format_journal,&
print_reference
USE reference_manager, ONLY: get_citation_key
USE string_utilities, ONLY: a2s,&
compress,&
substitute_special_xml_tokens,&
Expand All @@ -45,7 +43,7 @@ MODULE input_keyword_types

PUBLIC :: keyword_p_type, keyword_type, keyword_create, keyword_retain, &
keyword_release, keyword_get, keyword_describe, &
keyword_describe_html, write_keyword_xml, keyword_typo_match
write_keyword_xml, keyword_typo_match

! **************************************************************************************************
!> \brief represent a pointer to a keyword (to make arrays of pointers)
Expand Down Expand Up @@ -616,157 +614,6 @@ SUBROUTINE keyword_describe(keyword, unit_nr, level)
END IF
END SUBROUTINE keyword_describe

! **************************************************************************************************
!> \brief writes out a description of the keyword
!> \param keyword the keyword to describe
!> \param unit_nr the unit to write to
!> \author Joost VandeVondele [10.2004], based on keyword_describe
! **************************************************************************************************
SUBROUTINE keyword_describe_html(keyword, unit_nr)
TYPE(keyword_type), POINTER :: keyword
INTEGER, INTENT(in) :: unit_nr

CHARACTER(len=*), PARAMETER :: routineN = 'keyword_describe_html', &
routineP = moduleN//':'//routineN

CHARACTER(len=default_string_length) :: c_string, my_unit
INTEGER :: i, iref
LOGICAL :: any_description

CPASSERT(ASSOCIATED(keyword))
CPASSERT(keyword%ref_count > 0)
WRITE (unit_nr, '(a)') '<TR><TD WITDH="20%">'// &
'<A NAME="'//TRIM(keyword%names(1))//'"><u>'//TRIM(keyword%names(1))//'</u></A>'// &
'<TD WIDTH="80%">'
WRITE (unit_nr, '(a)') '<TR><TD WIDTH="20%"><TD WIDTH="80%">'//TRIM(keyword%usage)
WRITE (unit_nr, '(a)') '<TR><TD WIDTH="20%"><TD WIDTH="80%"><i>'//TRIM(a2s(keyword%description))//'</i>'
WRITE (unit_nr, "(a)", advance="NO") '<TR><TD WIDTH="10%"><TD> This keyword '
SELECT CASE (keyword%type_of_var)
CASE (logical_t)
IF (keyword%n_var == -1) THEN
WRITE (unit_nr, '(a)', ADVANCE="NO") 'expects a list of logicals'
ELSE IF (keyword%n_var == 1) THEN
WRITE (unit_nr, '(a)', ADVANCE="NO") 'expects a logical'
ELSE
WRITE (unit_nr, '(a,i6,a)', ADVANCE="NO") 'expects precisely', keyword%n_var, ' logicals'
END IF
! (provide a link to this info) WRITE(unit_nr,"(' (T,TRUE,YES,ON) and (F,FALSE,NO,OFF) are synonyms')")
CASE (integer_t)
IF (keyword%n_var == -1) THEN
WRITE (unit_nr, '(a)', ADVANCE="NO") 'expects a list of integers'
ELSE IF (keyword%n_var == 1) THEN
WRITE (unit_nr, '(a)', ADVANCE="NO") 'expects an integer'
ELSE
WRITE (unit_nr, '(a,i6,a)', ADVANCE="NO") 'expects precisely', keyword%n_var, ' integers'
END IF
CASE (real_t)
IF (keyword%n_var == -1) THEN
WRITE (unit_nr, '(a)', ADVANCE="NO") 'expects a list of reals'
ELSE IF (keyword%n_var == 1) THEN
WRITE (unit_nr, '(a)', ADVANCE="NO") 'expects a real'
ELSE
WRITE (unit_nr, '(a,i6,a)', ADVANCE="NO") 'expects precisely', keyword%n_var, ' reals'
END IF
CASE (char_t)
IF (keyword%n_var == -1) THEN
WRITE (unit_nr, '(a)', ADVANCE="NO") 'expects a list of words'
ELSE IF (keyword%n_var == 1) THEN
WRITE (unit_nr, '(a)', ADVANCE="NO") 'expects a word'
ELSE
WRITE (unit_nr, '(a,i6,a)', ADVANCE="NO") 'expects precisely', keyword%n_var, ' words'
END IF
CASE (lchar_t)
WRITE (unit_nr, '(a)', ADVANCE="NO") 'expects a string'
CASE (enum_t)
IF (keyword%n_var == -1) THEN
WRITE (unit_nr, '(a)', ADVANCE="NO") 'expects a list of keywords'
ELSE IF (keyword%n_var == 1) THEN
WRITE (unit_nr, '(a)', ADVANCE="NO") 'expects a keyword'
ELSE
WRITE (unit_nr, '(a,i6,a)', ADVANCE="NO") 'expects precisely', keyword%n_var, ' keywords'
END IF
CASE (no_t)
WRITE (unit_nr, '(a)', ADVANCE="NO") 'expects a non-standard input type'
CASE DEFAULT
CPABORT("")
END SELECT
IF (keyword%repeats) THEN
WRITE (unit_nr, "(', and may repeat')", ADVANCE="NO")
END IF
IF (ASSOCIATED(keyword%lone_keyword_value) .AND. keyword%type_of_var /= no_t) THEN
WRITE (unit_nr, '(a)', advance="NO") '<TR><TD WIDTH="10%"><TD>This keyword behaves as a switch'
CALL val_write(keyword%lone_keyword_value, unit_nr=unit_nr)
END IF
IF (ASSOCIATED(keyword%default_value) .AND. keyword%type_of_var /= no_t) THEN
IF (ASSOCIATED(keyword%unit)) THEN
my_unit = cp_unit_desc(keyword%unit, accept_undefined=.TRUE.)
WRITE (unit_nr, '(a)', advance="NO") '. Default unit: '//'['//TRIM(my_unit)//'], default value: '
ELSE
WRITE (unit_nr, '(a)', advance="NO") '. Default value: '
ENDIF
CALL val_write(keyword%default_value, unit=keyword%unit, unit_nr=unit_nr)
IF (ASSOCIATED(keyword%unit)) THEN
WRITE (unit_nr, '(a)', advance="NO") TRIM(my_unit)
END IF
ELSE
IF (ASSOCIATED(keyword%unit)) THEN
my_unit = cp_unit_desc(keyword%unit, accept_undefined=.TRUE.)
WRITE (unit_nr, '(a)', advance="NO") '. Default unit: '//'['//TRIM(my_unit)//'].'
END IF
ENDIF

IF (keyword%type_of_var == enum_t) THEN
any_description = .FALSE.
DO i = 1, SIZE(keyword%enum%c_vals)
any_description = any_description .OR. SIZE(keyword%enum%desc(i)%chars) > 1
ENDDO
IF (any_description) THEN
WRITE (unit_nr, '(a)', advance='NO') '<TR><TD WIDTH="10%"><TD> valid keywords:<ul> '
DO i = 1, SIZE(keyword%enum%c_vals)
c_string = keyword%enum%c_vals(i)
WRITE (unit_nr, '(a,a,a,a,a)') "<li><code>", &
TRIM(c_string), "</code>: ", TRIM(a2s(keyword%enum%desc(i)%chars)), "</li>"
END DO
WRITE (unit_nr, '(a)', advance='NO') '</ul>'
ELSE
WRITE (unit_nr, '(a)', advance='NO') '<TR><TD WIDTH="10%"><TD> valid keywords: '
IF (SIZE(keyword%enum%c_vals) > 0) &
WRITE (unit_nr, '(a)', advance='NO') TRIM(keyword%enum%c_vals(1))
DO i = 2, SIZE(keyword%enum%c_vals)
c_string = keyword%enum%c_vals(i)
WRITE (unit_nr, '(a)', advance='NO') ", "//TRIM(c_string)
END DO
ENDIF
IF (.NOT. keyword%enum%strict) THEN
WRITE (unit_nr, "(' other integer values are also accepted.')")
END IF
END IF
IF (SIZE(keyword%names) > 1) THEN
WRITE (unit_nr, "(a)", advance="NO") '<TR><TD WIDTH="10%"><TD>variants: '
DO i = 2, SIZE(keyword%names)
WRITE (unit_nr, "(a)", advance="NO") TRIM(keyword%names(i))
IF (i .NE. SIZE(keyword%names)) THEN
WRITE (unit_nr, '(a)', advance='NO') ', '
ENDIF
END DO
ENDIF
IF (ASSOCIATED(keyword%citations)) THEN
IF (SIZE(keyword%citations, 1) > 1) THEN
WRITE (unit_nr, FMT='(A)') '<BR> This keyword cites following references: '
ELSE
WRITE (unit_nr, FMT='(A)') '<BR> This keyword cites following reference: '
ENDIF
DO iref = 1, SIZE(keyword%citations, 1)
WRITE (unit_nr, FMT='(A,I0,A)') &
'<A HREF="references.html#reference_', keyword%citations(iref), '" TITLE="'
CALL print_reference(keyword%citations(iref), FORMAT=print_format_journal, unit=unit_nr)
WRITE (unit_nr, FMT='(A)') &
'">['//TRIM(get_citation_key(keyword%citations(iref)))//']</A>'
ENDDO
ENDIF

END SUBROUTINE keyword_describe_html

! **************************************************************************************************
!> \brief Prints a description of a keyword in XML format
!> \param keyword The keyword to describe
Expand Down
147 changes: 2 additions & 145 deletions src/input/input_section_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -11,15 +11,12 @@
!> \author fawzi
! **************************************************************************************************
MODULE input_section_types
USE cp_files, ONLY: close_file,&
open_file
USE cp_linked_list_input, ONLY: &
cp_sll_val_create, cp_sll_val_dealloc, cp_sll_val_get_el_at, cp_sll_val_get_length, &
cp_sll_val_get_rest, cp_sll_val_insert_el_at, cp_sll_val_next, cp_sll_val_p_type, &
cp_sll_val_rm_el_at, cp_sll_val_set_el_at, cp_sll_val_type
USE cp_log_handling, ONLY: cp_to_string
USE input_keyword_types, ONLY: keyword_describe,&
keyword_describe_html,&
keyword_p_type,&
keyword_release,&
keyword_retain,&
Expand All @@ -38,9 +35,7 @@ MODULE input_section_types
default_string_length,&
dp
USE print_messages, ONLY: print_message
USE reference_manager, ONLY: get_citation_key,&
print_format_journal,&
print_reference
USE reference_manager, ONLY: get_citation_key
USE string_utilities, ONLY: a2s,&
compress,&
substitute_special_xml_tokens,&
Expand All @@ -58,8 +53,7 @@ MODULE input_section_types
PUBLIC :: section_type
PUBLIC :: section_create, section_release, section_describe, &
section_get_subsection, section_get_keyword, &
section_add_keyword, section_add_subsection, section_describe_html, &
section_describe_index_html
section_add_keyword, section_add_subsection
PUBLIC :: section_get_subsection_index, section_get_keyword_index

PUBLIC :: section_vals_type
Expand Down Expand Up @@ -369,143 +363,6 @@ RECURSIVE SUBROUTINE section_describe(section, unit_nr, level, hide_root, recurs
END IF
END SUBROUTINE section_describe

! **************************************************************************************************
!> \brief ...
!> \param section ...
!> \param prefix ...
!> \param depth ...
!> \param unit_number ...
! **************************************************************************************************
RECURSIVE SUBROUTINE section_describe_html(section, prefix, depth, unit_number)
TYPE(section_type), POINTER :: section
CHARACTER(LEN=*), INTENT(IN) :: prefix
INTEGER, INTENT(in) :: depth, unit_number

CHARACTER(len=*), PARAMETER :: routineN = 'section_describe_html', &
routineP = moduleN//':'//routineN

CHARACTER(LEN=1000) :: local_prefix
CHARACTER(LEN=256), DIMENSION(50), SAVE :: location, name
CHARACTER(LEN=default_path_length) :: message
INTEGER :: idepth, ikeyword, iref, isub, unit_nr
LOGICAL :: has_keywords

IF (ASSOCIATED(section)) THEN
local_prefix = TRIM(prefix//"~"//TRIM(section%name))
CPASSERT(section%ref_count > 0)
CALL open_file(unit_number=unit_nr, file_name=TRIM(local_prefix)//".html", &
file_status="UNKNOWN", file_action="WRITE")
WRITE (unit_nr, FMT='(A)') "<HTML><BODY>"
WRITE (unit_nr, FMT='(A)') "<HEAD><TITLE> The CP2K project : input section "//section%name//"</TITLE></HEAD>"
WRITE (unit_nr, FMT='(A)') '<META NAME="description" content="CP2K">'
WRITE (unit_nr, FMT='(A)') &
'<META NAME="keywords" contents="scientific,computing,chemistry,physics,'// &
'documentation,help,manual,Fortran,parallel">'
WRITE (unit_nr, FMT='(A)') "<H1> Section "//section%name//" </H1>"
WRITE (unit_nr, FMT='(A)') ' <A HREF="index.html">Index of all sections</A>. This section is located at '
DO idepth = 1, depth
WRITE (unit_nr, FMT='(A)', ADVANCE="NO") '<A HREF="'//TRIM(location(idepth))//'">'//TRIM(name(idepth))//'</A>%'
ENDDO
location(depth+1) = TRIM(local_prefix)//".html"
name(depth+1) = TRIM(section%name)
WRITE (unit_nr, FMT='(A)') '<A HREF="'//TRIM(location(depth+1))//'">'//TRIM(name(depth+1))//'</A>.'

message = get_section_info(section)
WRITE (unit_nr, FMT='(A)') '<BR><BR>'//TRIM(a2s(section%description))//TRIM(message)

IF (ASSOCIATED(section%citations)) THEN
IF (SIZE(section%citations, 1) > 1) THEN
WRITE (unit_nr, FMT='(A)') '<BR><BR> This section cites following references: '
ELSE
WRITE (unit_nr, FMT='(A)') '<BR><BR> This section cites following reference: '
ENDIF
DO iref = 1, SIZE(section%citations, 1)
WRITE (unit_nr, FMT='(A,I0,A)') '<A HREF="references.html#reference_', section%citations(iref), '" TITLE="'
CALL print_reference(section%citations(iref), FORMAT=print_format_journal, unit=unit_nr)
WRITE (unit_nr, FMT='(A)') '">['//TRIM(get_citation_key(section%citations(iref)))//']</A>'
ENDDO
ENDIF

WRITE (unit_nr, FMT='(A)') "<H2> Subsections</H2>"
IF (section%n_subsections > 0) THEN
WRITE (unit_nr, FMT='(A)') "<UL>"
DO isub = 1, section%n_subsections
WRITE (unit_nr, FMT='(A)') &
'<LI><A HREF="'//TRIM(local_prefix)//"~"//TRIM(section%subsections(isub)%section%name)//".html"//'">'// &
TRIM(section%subsections(isub)%section%name)//' </A>'
END DO
WRITE (unit_nr, FMT='(A)') "</UL>"
ELSE
WRITE (unit_nr, FMT='(A)') "None"
ENDIF
WRITE (unit_nr, FMT='(A)') "<H2> Section keywords </H2>"
has_keywords = ASSOCIATED(section%keywords(-1)%keyword) .OR. &
ASSOCIATED(section%keywords(0)%keyword) .OR. &
section%n_keywords >= 1
IF (has_keywords) THEN
WRITE (unit_nr, FMT='(A)') "<UL>"
DO ikeyword = -1, section%n_keywords
IF (ASSOCIATED(section%keywords(ikeyword)%keyword)) THEN
WRITE (unit_nr, FMT='(A)') &
'<LI><A HREF="#'//TRIM(section%keywords(ikeyword)%keyword%names(1))//'">'// &
TRIM(section%keywords(ikeyword)%keyword%names(1))//" </A>"
END IF
END DO
WRITE (unit_nr, FMT='(A)') "</UL>"
WRITE (unit_nr, FMT='(A)') "<H2> Keyword descriptions </H2>"
WRITE (unit_nr, FMT='(A)') "<TABLE>"
DO ikeyword = -1, section%n_keywords
IF (ASSOCIATED(section%keywords(ikeyword)%keyword)) THEN
CALL keyword_describe_html(section%keywords(ikeyword)%keyword, unit_nr)
END IF
END DO
WRITE (unit_nr, FMT='(A)') "</TABLE>"
ELSE
WRITE (unit_nr, FMT='(A)') "None"
ENDIF
WRITE (unit_nr, FMT='(A)') &
'<BR><hr>Back to the <A HREF="https://www.cp2k.org/">CP2K homepage</A> or '// &
'the latest version of <A HREF="https://manual.cp2k.org/trunk/">this manual</A>'
WRITE (unit_nr, FMT='(A)') "</BODY></HTML>"
CALL close_file(unit_nr)
DO isub = 1, section%n_subsections
CALL section_describe_html(section%subsections(isub)%section, TRIM(local_prefix), depth+1, unit_number)
END DO
END IF
END SUBROUTINE section_describe_html

! **************************************************************************************************
!> \brief ...
!> \param section ...
!> \param prefix ...
!> \param unit_nr ...
! **************************************************************************************************
RECURSIVE SUBROUTINE section_describe_index_html(section, prefix, unit_nr)
TYPE(section_type), POINTER :: section
CHARACTER(LEN=*), INTENT(IN) :: prefix
INTEGER, INTENT(in) :: unit_nr

CHARACTER(len=*), PARAMETER :: routineN = 'section_describe_index_html', &
routineP = moduleN//':'//routineN

CHARACTER(LEN=1000) :: local_prefix
INTEGER :: isub

IF (ASSOCIATED(section)) THEN
CPASSERT(section%ref_count > 0)
local_prefix = TRIM(prefix//"~"//TRIM(section%name))
WRITE (unit_nr, FMT='(A)') &
'<LI><A HREF="'//TRIM(local_prefix)//'.html">'//TRIM(section%name)//"</A>"
IF (section%n_subsections > 0) THEN
WRITE (unit_nr, FMT='(A)') "<UL>"
DO isub = 1, section%n_subsections
CALL section_describe_index_html(section%subsections(isub)%section, TRIM(local_prefix), unit_nr)
END DO
WRITE (unit_nr, FMT='(A)') "</UL>"
ENDIF
ENDIF
END SUBROUTINE section_describe_index_html

! **************************************************************************************************
!> \brief returns the index of requested subsection (-1 if not found)
!> \param section the root section
Expand Down
Loading

0 comments on commit 2fba3c9

Please sign in to comment.