Skip to content

Commit

Permalink
parsing: add options to mark keywords as deprecated/removed
Browse files Browse the repository at this point in the history
  • Loading branch information
dev-zero committed Apr 24, 2020
1 parent 4019062 commit f2d83e1
Show file tree
Hide file tree
Showing 4 changed files with 81 additions and 73 deletions.
28 changes: 24 additions & 4 deletions src/input/input_keyword_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -62,13 +62,15 @@ MODULE input_keyword_types
!> \param usage how to use it "MAXSCF 10"
!> \param description what does it do: "MAXSCF : determines the maximum
!> number of steps in an SCF run"
!> \param deprecation_notice show this warning that the keyword is deprecated
!> \param citations references to literature associated with this keyword
!> \param type_of_var the type of keyword (controls how it is parsed)
!> it can be one of: no_parse_t,logical_t, integer_t, real_t,
!> char_t
!> \param n_var number of values that should be parsed (-1=unknown)
!> \param repeats if the keyword can be present more than once in the
!> section
!> \param removed to trigger a CPABORT when encountered while parsing the input
!> \param enum enumeration that defines the mapping between integers and
!> strings
!> \param unit the default unit this keyword is read in (to automatically
Expand All @@ -87,10 +89,11 @@ MODULE input_keyword_types
CHARACTER(LEN=default_string_length), DIMENSION(:), POINTER:: names
CHARACTER(LEN=usage_string_length) :: location
CHARACTER(LEN=usage_string_length) :: usage
CHARACTER, DIMENSION(:), POINTER :: description => Null()
CHARACTER, DIMENSION(:), POINTER :: description => null()
CHARACTER(LEN=:), ALLOCATABLE :: deprecation_notice
INTEGER, POINTER, DIMENSION(:) :: citations
INTEGER :: type_of_var, n_var
LOGICAL :: repeats
LOGICAL :: repeats, removed
TYPE(enumeration_type), POINTER :: enum
TYPE(cp_unit_type), POINTER :: unit
TYPE(val_type), POINTER :: default_value
Expand Down Expand Up @@ -136,6 +139,8 @@ MODULE input_keyword_types
!> \param enum_desc ...
!> \param unit_str ...
!> \param citations ...
!> \param deprecation_notice ...
!> \param removed ...
!> \author fawzi
! **************************************************************************************************
SUBROUTINE keyword_create(keyword, location, name, description, usage, type_of_var, &
Expand All @@ -145,7 +150,7 @@ SUBROUTINE keyword_create(keyword, location, name, description, usage, type_of_v
lone_keyword_val, lone_keyword_l_val, lone_keyword_r_val, lone_keyword_c_val, &
lone_keyword_i_val, lone_keyword_l_vals, lone_keyword_r_vals, &
lone_keyword_c_vals, lone_keyword_i_vals, enum_c_vals, enum_i_vals, &
enum, enum_strict, enum_desc, unit_str, citations)
enum, enum_strict, enum_desc, unit_str, citations, deprecation_notice, removed)
TYPE(keyword_type), POINTER :: keyword
CHARACTER(len=*), INTENT(in) :: location, name, description
CHARACTER(len=*), INTENT(in), OPTIONAL :: usage
Expand Down Expand Up @@ -182,6 +187,8 @@ SUBROUTINE keyword_create(keyword, location, name, description, usage, type_of_v
OPTIONAL :: enum_desc
CHARACTER(len=*), INTENT(in), OPTIONAL :: unit_str
INTEGER, DIMENSION(:), INTENT(in), OPTIONAL :: citations
CHARACTER(len=*), INTENT(in), OPTIONAL :: deprecation_notice
LOGICAL, INTENT(in), OPTIONAL :: removed

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

Expand All @@ -195,6 +202,7 @@ SUBROUTINE keyword_create(keyword, location, name, description, usage, type_of_v
keyword%id_nr = last_keyword_id
NULLIFY (keyword%unit)
keyword%location = location
keyword%removed = .FALSE.

IF (PRESENT(variants)) THEN
ALLOCATE (keyword%names(SIZE(variants) + 1))
Expand Down Expand Up @@ -385,6 +393,14 @@ SUBROUTINE keyword_create(keyword, location, name, description, usage, type_of_v
IF (PRESENT(unit_str)) THEN
CALL cp_unit_create(keyword%unit, unit_str)
END IF

IF (PRESENT(deprecation_notice)) THEN
keyword%deprecation_notice = TRIM(deprecation_notice)
END IF

IF (PRESENT(removed)) THEN
keyword%removed = removed
END IF
END SUBROUTINE keyword_create

! **************************************************************************************************
Expand Down Expand Up @@ -731,6 +747,11 @@ SUBROUTINE write_keyword_xml(keyword, level, unit_number)
TRIM(substitute_special_xml_tokens(a2s(keyword%description))) &
//"</DESCRIPTION>"

IF (ALLOCATED(keyword%deprecation_notice)) &
WRITE (UNIT=unit_number, FMT="(A)") REPEAT(" ", l1)//"<DEPRECATION_NOTICE>"// &
TRIM(substitute_special_xml_tokens(keyword%deprecation_notice)) &
//"</DEPRECATION_NOTICE>"

IF (ASSOCIATED(keyword%default_value) .AND. &
(keyword%type_of_var /= no_t)) THEN
IF (ASSOCIATED(keyword%unit)) THEN
Expand Down Expand Up @@ -864,4 +885,3 @@ SUBROUTINE keyword_typo_match(keyword, unknown_string, location_string, matching
END SUBROUTINE keyword_typo_match

END MODULE input_keyword_types

18 changes: 18 additions & 0 deletions src/input/input_parsing.F
Original file line number Diff line number Diff line change
Expand Up @@ -251,6 +251,24 @@ RECURSIVE SUBROUTINE section_vals_parse(section_vals, parser, default_units, roo
END IF
keyword => section%keywords(ik)%keyword
IF (ASSOCIATED(keyword)) THEN
IF (keyword%removed) THEN
IF (ALLOCATED(keyword%deprecation_notice)) THEN
CALL cp_abort(__LOCATION__, &
"The specified keyword '"//TRIM(token)//"' is not available anymore: "// &
keyword%deprecation_notice)
ELSE
CALL cp_abort(__LOCATION__, &
"The specified keyword '"//TRIM(token)// &
"' is not available anymore, please consult the manual.")
END IF
END IF
IF (ALLOCATED(keyword%deprecation_notice)) &
CALL cp_warn(__LOCATION__, &
"The specified keyword '"//TRIM(token)// &
"' is deprecated and may be removed in a future version: "// &
keyword%deprecation_notice//".")
NULLIFY (el)
IF (ik /= 0 .AND. keyword%type_of_var == lchar_t) &
CALL parser_skip_space(parser)
Expand Down
48 changes: 30 additions & 18 deletions src/input_cp2k_subsys.F
Original file line number Diff line number Diff line change
Expand Up @@ -1087,37 +1087,48 @@ SUBROUTINE create_kind_section(section)

! old type basis set input keywords
! kept for backward compatibility
CALL keyword_create(keyword, __LOCATION__, name="AUX_BASIS_SET", &
variants=s2a("AUXILIARY_BASIS_SET", "AUX_BASIS"), &
description="DEPRECATED (use BASIS_SET): The auxiliary basis set (GTO type)", &
usage="AUX_BASIS_SET DZVP", default_c_val=" ", &
n_var=1)
CALL keyword_create( &
keyword, __LOCATION__, name="AUX_BASIS_SET", &
variants=s2a("AUXILIARY_BASIS_SET", "AUX_BASIS"), &
description="The auxiliary basis set (GTO type)", &
usage="AUX_BASIS_SET DZVP", default_c_val=" ", &
n_var=1, &
deprecation_notice="use 'BASIS_SET AUX ...' instead", &
removed=.TRUE.)
CALL section_add_keyword(section, keyword)
CALL keyword_release(keyword)

CALL keyword_create(keyword, __LOCATION__, name="RI_AUX_BASIS_SET", &
variants=s2a("RI_MP2_BASIS_SET", "RI_RPA_BASIS_SET", "RI_AUX_BASIS"), &
description="DEPRECATED (use BASIS_SET): The RI auxiliary basis set used in WF_CORRELATION (GTO type)", &
usage="RI_AUX_BASIS_SET DZVP", default_c_val=" ", &
n_var=1)
CALL keyword_create( &
keyword, __LOCATION__, name="RI_AUX_BASIS_SET", &
variants=s2a("RI_MP2_BASIS_SET", "RI_RPA_BASIS_SET", "RI_AUX_BASIS"), &
description="The RI auxiliary basis set used in WF_CORRELATION (GTO type)", &
usage="RI_AUX_BASIS_SET DZVP", default_c_val=" ", &
n_var=1, &
deprecation_notice="use 'BASIS_SET RI_AUX ...' instead", &
removed=.TRUE.)
CALL section_add_keyword(section, keyword)
CALL keyword_release(keyword)

CALL keyword_create(keyword, __LOCATION__, name="LRI_BASIS_SET", &
variants=s2a("LRI_BASIS"), &
description="DEPRECATED (use BASIS_SET): The local resolution of identity basis set (GTO type)", &
usage="", default_c_val=" ", &
n_var=1)
CALL keyword_create( &
keyword, __LOCATION__, name="LRI_BASIS_SET", &
variants=s2a("LRI_BASIS"), &
description="The local resolution of identity basis set (GTO type)", &
usage="", default_c_val=" ", &
n_var=1, &
deprecation_notice="use 'BASIS_SET AUX_FIT ...' instead", &
removed=.TRUE.)
CALL section_add_keyword(section, keyword)
CALL keyword_release(keyword)

CALL keyword_create( &
keyword, __LOCATION__, name="AUX_FIT_BASIS_SET", &
variants=s2a("AUXILIARY_FIT_BASIS_SET", "AUX_FIT_BASIS"), &
description="DEPRECATED (use BASIS_SET): The auxiliary basis set (GTO type) for auxiliary density matrix method", &
description="The auxiliary basis set (GTO type) for auxiliary density matrix method", &
usage="AUX_FIT_BASIS_SET DZVP", default_c_val=" ", &
citations=(/Guidon2010/), &
n_var=1)
n_var=1, &
deprecation_notice="use 'BASIS_SET AUX_FIT ...' instead", &
removed=.TRUE.)
CALL section_add_keyword(section, keyword)
CALL keyword_release(keyword)
! end of old basis set keywords
Expand Down Expand Up @@ -1170,13 +1181,14 @@ SUBROUTINE create_kind_section(section)

CALL keyword_create(keyword, __LOCATION__, name="POTENTIAL_TYPE", &
description="The type of this kinds pseudopotential (ECP, ALL, GTH, UPS).", &
deprecation_notice="use 'POTENTIAL <TYPE> ...' instead", &
usage="POTENTIAL_TYPE <TYPE>", default_c_val="", n_var=1)
CALL section_add_keyword(section, keyword)
CALL keyword_release(keyword)

CALL keyword_create(keyword, __LOCATION__, name="POTENTIAL", &
variants=(/"POT"/), &
description="The type and name of the pseudopotential for the defined kind.", &
description="The type (ECP, ALL, GTH, UPS) and name of the pseudopotential for the defined kind.", &
usage="POTENTIAL [type] <POTENTIAL-NAME>", type_of_var=char_t, default_c_vals=(/" ", " "/), &
citations=(/Goedecker1996, Hartwigsen1998, Krack2005/), n_var=-1)
CALL section_add_keyword(section, keyword)
Expand Down
60 changes: 9 additions & 51 deletions src/qs_kind_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -1426,9 +1426,9 @@ SUBROUTINE read_qs_kind(qs_kind, kind_section, para_env, force_env_section, &
CHARACTER(LEN=2) :: element_symbol
CHARACTER(len=default_path_length) :: kg_potential_fn_kind, &
potential_file_name, potential_fn_kind
CHARACTER(LEN=default_string_length) :: akind_name, aux_basis_set_name, &
aux_fit_basis_set_name, basis_type, keyword, kgpot_name, kgpot_type, lri_basis_set_name, &
orb_basis_set_name, potential_name, potential_type, ri_aux_basis_set_name, tmp
CHARACTER(LEN=default_string_length) :: akind_name, basis_type, keyword, &
kgpot_name, kgpot_type, &
potential_name, potential_type, tmp
CHARACTER(LEN=default_string_length), DIMENSION(4) :: description
CHARACTER(LEN=default_string_length), &
DIMENSION(:), POINTER :: tmpstringlist
Expand Down Expand Up @@ -1467,9 +1467,6 @@ SUBROUTINE read_qs_kind(qs_kind, kind_section, para_env, force_env_section, &
basis_set_name(:) = ""
basis_set_type(:) = ""
basis_set_form(:) = ""
aux_basis_set_name = ""
ri_aux_basis_set_name = ""
orb_basis_set_name = ""
potential_name = ""
potential_type = ""
kgpot_name = ""
Expand Down Expand Up @@ -1577,54 +1574,15 @@ SUBROUTINE read_qs_kind(qs_kind, kind_section, para_env, force_env_section, &
basis_set_form(i) = tmpstringlist(2)
basis_set_name(i) = tmpstringlist(3)
ELSE
CPABORT("")
CALL cp_abort(__LOCATION__, &
"invalid number of BASIS_SET keyword parameters: BASIS_SET [<TYPE>] [<FORM>] <NAME>")
END IF
! check that we have a valid basis set form
IF (basis_set_form(i) /= "GTO" .AND. basis_set_form(i) /= "STO") THEN
CPABORT("BASIS_SET_FORM invalid")
CPABORT("invalid BASIS_SET FORM parameter")
END IF
END DO
! Deprecated keywords
DO i = 1, nb_rep
IF (basis_set_type(i) == "ORB") THEN
orb_basis_set_name = basis_set_name(i)
EXIT
END IF
END DO
!
CALL section_vals_val_get(kind_section, i_rep_section=k_rep, &
keyword_name="AUX_FIT_BASIS_SET", c_val=aux_fit_basis_set_name)
IF (aux_fit_basis_set_name /= "") THEN
CPWARN("AUX_FIT_BASIS_SET Keyword cannot be used any longer, use BASIS_SET AUX_FIT")
CPABORT("AUX_FIT_BASIS_SET")
END IF
!
CALL section_vals_val_get(kind_section, i_rep_section=k_rep, &
keyword_name="AUX_BASIS_SET", c_val=aux_basis_set_name)
IF (aux_basis_set_name /= "") THEN
CPWARN("AUX_BASIS_SET Keyword cannot be used any longer, use BASIS_SET AUX")
CPABORT("AUX_BASIS_SET")
END IF
!
CALL section_vals_val_get(kind_section, i_rep_section=k_rep, &
keyword_name="LRI_BASIS_SET", c_val=lri_basis_set_name)
IF (lri_basis_set_name /= "") THEN
CPWARN("LRI_BASIS_SET Keyword cannot be used any longer, use BASIS_SET LRI")
CPABORT("LRI_BASIS_SET")
END IF
!
CALL section_vals_val_get(kind_section, i_rep_section=k_rep, &
keyword_name="RI_AUX_BASIS_SET", c_val=ri_aux_basis_set_name)
IF (ri_aux_basis_set_name /= "") THEN
nb_rep = nb_rep + 1
CPASSERT(nb_rep <= maxbas)
basis_set_type(nb_rep) = "RI_AUX"
basis_set_form(nb_rep) = "GTO"
basis_set_name(nb_rep) = ri_aux_basis_set_name
END IF
! end of deprecated input
! parse PAO_BASIS_SIZE
CALL section_vals_val_get(kind_section, keyword_name="PAO_BASIS_SIZE", i_rep_section=k_rep, &
i_val=qs_kind%pao_basis_size)
Expand Down Expand Up @@ -2008,7 +1966,7 @@ SUBROUTINE read_qs_kind(qs_kind, kind_section, para_env, force_env_section, &
"Information provided in the input file regarding POTENTIAL for KIND <"// &
TRIM(qs_kind%name)//"> will be ignored!")
check = ((orb_basis_set_name /= '') .OR. explicit_basis)
check = ((nb_rep > 0) .OR. explicit_basis)
IF (check) &
CALL cp_warn(__LOCATION__, &
"Information provided in the input file regarding BASIS for KIND <"// &
Expand Down Expand Up @@ -2041,7 +1999,7 @@ SUBROUTINE read_qs_kind(qs_kind, kind_section, para_env, force_env_section, &
"Information provided in the input file regarding POTENTIAL for KIND <"// &
TRIM(qs_kind%name)//"> will be ignored!")
check = ((orb_basis_set_name /= '') .OR. explicit_basis)
check = ((nb_rep > 0) .OR. explicit_basis)
IF (check) &
CALL cp_warn(__LOCATION__, &
"Information provided in the input file regarding BASIS for KIND <"// &
Expand Down Expand Up @@ -2074,7 +2032,7 @@ SUBROUTINE read_qs_kind(qs_kind, kind_section, para_env, force_env_section, &
"Information provided in the input file regarding POTENTIAL for KIND <"// &
TRIM(qs_kind%name)//"> will be ignored!")
check = ((orb_basis_set_name /= '') .OR. explicit_basis)
check = ((nb_rep > 0) .OR. explicit_basis)
IF (check) &
CALL cp_warn(__LOCATION__, &
"Information provided in the input file regarding BASIS for KIND <"// &
Expand Down

0 comments on commit f2d83e1

Please sign in to comment.