Skip to content

Commit

Permalink
Remove version number from development branch
Browse files Browse the repository at this point in the history
  • Loading branch information
oschuett committed Jul 8, 2022
1 parent 20fe009 commit f1821e6
Show file tree
Hide file tree
Showing 5 changed files with 11 additions and 44 deletions.
16 changes: 3 additions & 13 deletions src/cp2k_info.F
Original file line number Diff line number Diff line change
Expand Up @@ -15,8 +15,6 @@
! **************************************************************************************************
MODULE cp2k_info

USE input_constants, ONLY: id_development_version,&
id_release_version
USE kinds, ONLY: default_path_length,&
default_string_length
USE machine, ONLY: m_datum,&
Expand All @@ -29,27 +27,19 @@ MODULE cp2k_info
IMPLICIT NONE
PRIVATE

PUBLIC :: cp2k_year, cp2k_version, cp2k_home, id_cp2k_version, cp2k_flags
PUBLIC :: cp2k_version, cp2k_year, cp2k_home, cp2k_flags
PUBLIC :: compile_arch, compile_date, compile_host, compile_revision
PUBLIC :: print_cp2k_license, get_runtime_info, write_restart_header

! the version string of CP2K intended to be adjust after releases and branches
#if defined(__RELEASE_VERSION)
INTEGER, PARAMETER :: id_cp2k_version = id_release_version ! (Uncomment for release version)
#else
INTEGER, PARAMETER :: id_cp2k_version = id_development_version ! (Uncomment for development version)
! INTEGER, PARAMETER :: id_cp2k_version = 2 ! (Uncomment for branch version)
#endif

#if defined(__COMPILE_REVISION)
CHARACTER(LEN=*), PARAMETER :: compile_revision = __COMPILE_REVISION
#else
CHARACTER(LEN=*), PARAMETER :: compile_revision = "unknown"
#endif

CHARACTER(LEN=*), PARAMETER :: version_nr = "10.0"
! The cp2k_version string should be changed for release branches.
CHARACTER(LEN=*), PARAMETER :: cp2k_version = "CP2K development version"
CHARACTER(LEN=*), PARAMETER :: cp2k_year = "2022"
CHARACTER(LEN=*), PARAMETER :: cp2k_version = "CP2K version "//TRIM(version_nr)
CHARACTER(LEN=*), PARAMETER :: cp2k_home = "https://www.cp2k.org/"

! compile time information
Expand Down
18 changes: 4 additions & 14 deletions src/environment.F
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ MODULE environment
cite_reference
USE cp2k_info, ONLY: &
compile_arch, compile_date, compile_host, compile_revision, cp2k_flags, cp2k_home, &
cp2k_version, cp2k_year, get_runtime_info, id_cp2k_version, r_host_name, r_pid, r_user_name
cp2k_version, cp2k_year, get_runtime_info, r_host_name, r_pid, r_user_name
USE cp_error_handling, ONLY: warning_counter
USE cp_files, ONLY: close_file,&
get_data_dir,&
Expand Down Expand Up @@ -61,7 +61,7 @@ MODULE environment
USE input_constants, ONLY: &
callgraph_all, callgraph_none, do_cosma, do_cp2k, do_diag_elpa, do_diag_scalapack, do_eip, &
do_farming, do_fft_fftw3, do_fft_sg, do_fist, do_qs, do_scalapack, do_sirius, do_test, &
energy_run, id_development_version, mol_dyn_run, none_run
energy_run, mol_dyn_run, none_run
USE input_cp2k_global, ONLY: create_global_section
USE input_enumeration_types, ONLY: enum_i2c,&
enumeration_type
Expand Down Expand Up @@ -148,7 +148,6 @@ SUBROUTINE cp2k_init(para_env, output_unit, globenv, input_file_name, wdir)
CHARACTER(LEN=*), OPTIONAL :: wdir

CHARACTER(LEN=10*default_string_length) :: cp_flags
CHARACTER(LEN=default_string_length) :: dev_flag
INTEGER :: i, ilen, my_output_unit
TYPE(cp_logger_type), POINTER :: logger

Expand All @@ -159,10 +158,6 @@ SUBROUTINE cp2k_init(para_env, output_unit, globenv, input_file_name, wdir)
! Message passing performance
CALL add_mp_perf_env()

! Set flag if this is a development version
dev_flag = ""
IF (id_cp2k_version == id_development_version) dev_flag = " (Development Version)"

! Init the default logger
IF (para_env%ionode) THEN
my_output_unit = output_unit
Expand All @@ -184,8 +179,7 @@ SUBROUTINE cp2k_init(para_env, output_unit, globenv, input_file_name, wdir)

IF (my_output_unit > 0) THEN
WRITE (UNIT=my_output_unit, FMT="(/,T2,A,T31,A50)") &
"CP2K| version string: ", &
ADJUSTR(TRIM(cp2k_version)//TRIM(dev_flag))
"CP2K| version string: ", ADJUSTR(TRIM(cp2k_version))
WRITE (UNIT=my_output_unit, FMT="(T2,A,T41,A40)") &
"CP2K| source code revision number:", &
ADJUSTR(compile_revision)
Expand Down Expand Up @@ -1152,7 +1146,6 @@ SUBROUTINE cp2k_finalize(root_section, para_env, globenv, wdir, q_finalize)
LOGICAL, INTENT(IN), OPTIONAL :: q_finalize
CHARACTER(LEN=default_path_length) :: cg_filename
CHARACTER(LEN=default_string_length) :: dev_flag
INTEGER :: cg_mode, iw, unit_exit
LOGICAL :: delete_it, do_finalize, report_maxloc, &
sort_by_self_time
Expand All @@ -1163,9 +1156,6 @@ SUBROUTINE cp2k_finalize(root_section, para_env, globenv, wdir, q_finalize)
! i.e. the input is most likely not available
! Set flag if this is a development version
dev_flag = ""
IF (id_cp2k_version == id_development_version) dev_flag = " (Development Version)"
do_finalize = .TRUE.
IF (PRESENT(q_finalize)) do_finalize = q_finalize
! Clean up
Expand Down Expand Up @@ -1200,7 +1190,7 @@ SUBROUTINE cp2k_finalize(root_section, para_env, globenv, wdir, q_finalize)
WRITE (UNIT=iw, FMT="(T2,A)") REPEAT("-", 79)
WRITE (UNIT=iw, FMT="(T2,A)") ""
WRITE (UNIT=iw, FMT="(T2,A)") TRIM(cp2k_version)//TRIM(dev_flag)//", the CP2K developers group ("//TRIM(cp2k_year)//")."
WRITE (UNIT=iw, FMT="(T2,A)") TRIM(cp2k_version)//", the CP2K developers group ("//TRIM(cp2k_year)//")."
WRITE (UNIT=iw, FMT="(T2,A)") "CP2K is freely available from "//TRIM(cp2k_home)//" ."
CALL print_all_references(sorted=.TRUE., cited_only=.TRUE., &
Expand Down
12 changes: 2 additions & 10 deletions src/start/cp2k.F
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,6 @@ PROGRAM cp2k
USE cp2k_info, ONLY: compile_revision,&
cp2k_flags,&
cp2k_version,&
id_cp2k_version,&
print_cp2k_license
USE cp2k_runs, ONLY: run_input,&
write_xml_file
Expand All @@ -56,22 +55,19 @@ PROGRAM cp2k
default_para_env,&
finalize_cp2k,&
init_cp2k
USE input_constants, ONLY: id_development_version
USE input_cp2k, ONLY: create_cp2k_root_section
USE input_section_types, ONLY: section_release,&
section_type
USE iso_fortran_env, ONLY: compiler_options,&
compiler_version
USE kinds, ONLY: default_path_length,&
default_string_length
USE kinds, ONLY: default_path_length
USE machine, ONLY: default_output_unit
#include "../base/base_uses.f90"

IMPLICIT NONE

CHARACTER(LEN=default_path_length) :: input_file_name, output_file_name, &
arg_att, command
CHARACTER(LEN=default_string_length) :: dev_flag
CHARACTER(LEN=default_path_length), &
DIMENSION(:, :), ALLOCATABLE :: initial_variables, initial_variables_tmp
CHARACTER(LEN=:), ALLOCATABLE :: compiler_options_string
Expand Down Expand Up @@ -329,11 +325,7 @@ PROGRAM cp2k
! write the version string
IF (print_version) THEN
IF (default_para_env%ionode) THEN
dev_flag = ""
IF (id_cp2k_version == id_development_version) &
dev_flag = " (Development Version)"
WRITE (output_unit, "(T2,A)") &
cp2k_version//TRIM(dev_flag), &
WRITE (output_unit, "(T2,A)") cp2k_version, &
"Source code revision "//TRIM(compile_revision), &
TRIM(cp2k_flags())
compiler_options_string = compiler_options()
Expand Down
8 changes: 2 additions & 6 deletions src/start/cp2k_shell.F
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,6 @@ MODULE cp2k_shell
compile_revision,&
cp2k_home,&
cp2k_version,&
id_cp2k_version,&
print_cp2k_license
USE cp2k_runs, ONLY: run_input
USE cp_files, ONLY: close_file,&
Expand All @@ -50,7 +49,6 @@ MODULE cp2k_shell
USE f77_interface, ONLY: &
calc_energy_force, calc_force, create_force_env, destroy_force_env, get_cell, get_energy, &
get_force, get_natom, get_pos, get_stress_tensor, set_cell, set_pos
USE input_constants, ONLY: id_development_version
USE input_cp2k_read, ONLY: empty_initial_variables
USE input_section_types, ONLY: section_type
USE kinds, ONLY: default_path_length,&
Expand Down Expand Up @@ -359,16 +357,14 @@ END SUBROUTINE help_command
SUBROUTINE info_license_command(shell)
TYPE(cp2k_shell_type) :: shell

CHARACTER(LEN=default_path_length) :: cwd, dev_flag, host_name, user_name
CHARACTER(LEN=default_path_length) :: cwd, host_name, user_name
INTEGER :: pid

IF (shell%iw > 0) THEN
CALL m_getcwd(cwd)
CALL m_getpid(pid)
CALL m_getlog(user_name)
CALL m_hostnm(host_name)
dev_flag = ""
IF (id_cp2k_version == id_development_version) dev_flag = " (Development Version)"
WRITE (UNIT=shell%iw, FMT="(A,A)") &
" PROGRAM STARTED ON ", TRIM(host_name)
WRITE (UNIT=shell%iw, FMT="(A,A)") &
Expand All @@ -379,7 +375,7 @@ SUBROUTINE info_license_command(shell)
" PROGRAM STARTED IN ", TRIM(cwd)
WRITE (UNIT=shell%iw, FMT="(/,T2,A,T31,A50)") &
"CP2K| version string: ", &
ADJUSTR(TRIM(cp2k_version)//TRIM(dev_flag))
ADJUSTR(TRIM(cp2k_version))
WRITE (UNIT=shell%iw, FMT="(T2,A,T41,A40)") &
"CP2K| source code revision number:", &
ADJUSTR(compile_revision)
Expand Down
1 change: 0 additions & 1 deletion tools/precommit/check_file_properties.py
Original file line number Diff line number Diff line change
Expand Up @@ -54,7 +54,6 @@
r"__PILAENV_BLOCKSIZE",
r"__PW_CUDA_NO_HOSTALLOC",
r"__PW_CUDA_NO_HOSTALLOC",
r"__RELEASE_VERSION",
r"__T_C_G0",
r"__YUKAWA",
r"__cplusplus",
Expand Down

0 comments on commit f1821e6

Please sign in to comment.