Skip to content

Commit

Permalink
Fix warnings (#41)
Browse files Browse the repository at this point in the history
  • Loading branch information
foxtran authored Oct 4, 2024
1 parent 97019d7 commit 647105c
Show file tree
Hide file tree
Showing 8 changed files with 92 additions and 110 deletions.
106 changes: 50 additions & 56 deletions app/main.f90
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,6 @@ program CPCMX
use, intrinsic :: iso_fortran_env, only : output_unit, error_unit, input_unit
implicit none
character(len=*), parameter :: prog_name = "cpx"
logical :: ex
integer :: ioerror

real(wp), allocatable :: isodens_rad(:)
Expand All @@ -36,13 +35,12 @@ program CPCMX

type(calculation_type) :: calc
type(configuration_type) :: config
type(parameter_type) :: parameter
type(error_type), allocatable :: error




!! ------------------------------------------------------------


!! ------------------------------------------------------------
!! Read Command Line Arguments and set Parameters accordingly
!! ------------------------------------------------------------
Call timer%push("total")
Expand All @@ -54,7 +52,7 @@ program CPCMX
else
Call initialize_param(config%sac_param_path,calc%param,error)
end if
Call check_error(error)
Call check_error(error)
if (config%ML) then
Call init_pr
write(*,*) "Machine Learning Mode selected. Will Only Write an ML.data file." !! ML Mode deprecated
Expand All @@ -69,10 +67,10 @@ program CPCMX
! write(*,*) "Reading Sigma Profile"
! Call read_singlesig(solvent_sigma,config%csm_solvent,solvent_volume)
! Call read_singlesig(solute_sigma,config%csm_solute,solute_volume)
!
!
! Call read_triplesig(solvent_sigma3,config%csm_solvent,solvent_volume)
! Call read_triplesig(solute_sigma3,config%csm_solute,solute_volume)
!else
!else
!! ----------------------------------------------------------------------------------
!! Creating COSMO Files with QC packages
!! ----------------------------------------------------------------------------------
Expand All @@ -92,12 +90,12 @@ program CPCMX
error stop
end select
Call check_error(error)
Call timer%pop()
end if
Call timer%pop()
end if
!! ----------------------------------------------------------------------------------
!! Create the Sigma Profile from COSMO files
!! ----------------------------------------------------------------------------------

Call timer%push("sigma_av")
!! ------------------------------------------------------------------------------------
!! Read necessary COSMO Data
Expand All @@ -116,7 +114,7 @@ program CPCMX
call check_error(error)
Call read_cosmo(config%csm_solute,calc%solute,config%database,error)
call check_error(error)

!! ------------------------------------------------------------------------------------
!! Sigma Charge Averaging and creating of a single Sigma Profile for Solute and Solvent
!! ------------------------------------------------------------------------------------
Expand All @@ -130,7 +128,7 @@ program CPCMX
!! Determination of Atoms in Rings, necessary for the PR2018 EOS and ER Correction
!! ------------------------------------------------------------------------------------
if ((config%ML) .OR. (.NOT. config%model .EQ. "sac")) then
Call timer%push("bondings")
Call timer%push("bondings")
write(output_unit,'(5x,a)') "Determine Ring atoms and HB groups."
Call calc%init_bonding()
Call timer%pop()
Expand All @@ -147,14 +145,14 @@ program CPCMX
end if

!! ------------------------------------------------------------------------------------
!! Exit here if you only want Sigma Profiles to be created
!! Exit here if you only want Sigma Profiles to be created
!! ------------------------------------------------------------------------------------
if (config%prof) then;
write(*,*) "Only Profile mode choosen, exiting."
stop
end if
!end if


!! ------------------------------------------------------------------------------------
!! Choice of the different post COSMO Models (sac,sac2010,sac2013,CPCM-X)
Expand All @@ -179,7 +177,7 @@ program CPCMX
! &config%smd_solvent,config%smd_param_path,config%smd_default)
!
! case("sac2010")
!
!
! Call sac_gas(solute_energy,id_scr,solute_area,solute_sv,solute_su,solute_pot)
! Call sac_2010(solvent_sigma3,solute_sigma3,solvent_volume,solute_volume)
! if (config%ML) Call pr2018(solute_area,solute_elements,solute_ident,oh_sol,nh_sol,near_sol)
Expand All @@ -202,7 +200,7 @@ program CPCMX
! Call sac_2013(solvent_sigma3,solute_sigma3,solvent_volume,solute_volume,sac_disp)
! Call pr2018(solute_area,solute_elements,solute_ident,oh_sol,nh_sol,near_sol)
! case ("crs")

!! CPCM-RS calculation starts here !!

! Calculation of Solvent Phase energies
Expand All @@ -226,7 +224,7 @@ program CPCMX
"| Gas Phase Results |",&
" ------------------------------------------------- ", &
""

write(output_unit,'(5x,a,t30,F15.8,2x,a)') &
"E_COSMO:", calc%solute%energy, "Eh", &
"E_COSMO+dE:", (calc%solute%energy+calc%dG_cc),"Eh", &
Expand All @@ -241,7 +239,7 @@ program CPCMX
"Solvent atomic mass:", AtomicMass(calc%solvent%element), "a.u.", &
"State correction", calc%dG_ss, "Eh", &
""

Call timer%push("cds")
if (config%isodens) then
Call get_isodens_radii(calc%solute%xyz,calc%solute%id,calc%solute%atom_xyz,isodens_rad)
Expand All @@ -250,13 +248,13 @@ program CPCMX
"| Isodensity Radii |",&
" ------------------------------------------------- ", &
""
write(output_unit,'(5x,a)'), &
write(output_unit,'(5x,a)') &
"Isodensity Flag used, calculated isodensity radii:",&
""
write(output_unit,'(10x,a,t30,a)'), &
write(output_unit,'(10x,a,t30,a)') &
"Atom Number:", "[A]"
do i=1,maxval(calc%solute%id)
write(output_unit,'(10x,I0,t30,F4.2)'),&
write(output_unit,'(10x,I0,t30,F4.2)') &
i, isodens_rad(i)
end do
write(output_unit,'(a)') ""
Expand All @@ -273,13 +271,13 @@ program CPCMX
Call timer%pop()

!end select

write(output_unit,'(10x,a)') &
" ------------------------------------------------- ",&
"| Results |",&
" ------------------------------------------------- ", &
""

if (config%ML) then
write(*,*) "Writing ML data in ML.data"
Call System("paste --delimiters='' ML.energy ML.gamma ML.pr > ML.data")
Expand Down Expand Up @@ -319,7 +317,7 @@ program CPCMX
write(*,*) "total"//repeat(" ", 18)//format_time(ttime)
do i = 1,size(label)
stime = timer%get(label(i))
write(*,*) label(i)//repeat(" ",3)//format_time(stime)
write(*,*) label(i)//repeat(" ",3)//format_time(stime)
end do
end block
end if
Expand All @@ -345,7 +343,7 @@ subroutine help(unit)
" --inp", "Allows to specify an input file for advanced configuration.", &
" --help", "Show this help message"
write(unit, '(a)')

end subroutine help

subroutine sample(filename,rc)
Expand Down Expand Up @@ -433,20 +431,19 @@ subroutine get_arguments(config, error)
type(error_type), allocatable, intent(out) :: error

integer :: iarg, narg
real(wp) :: val
character(len=:), allocatable :: arg, home
logical :: ex


Call get_variable("CPXHOME",home)

if (.not.allocated(home)) then
Call move_line("/",home)
else
if (home(len(home):len(home)) .ne. "/") call move_line(home//"/",home)
end if
ex=.false.


config%isodens=.false.
iarg = 0
Expand Down Expand Up @@ -480,7 +477,7 @@ subroutine get_arguments(config, error)
end if
call fatal_error(error, "Too many positional arguments present")
exit
case ("--prog")
case ("--prog")
iarg=iarg+1
call get_argument(iarg,arg)
call move_alloc(arg, config%qc_calc)
Expand Down Expand Up @@ -521,7 +518,7 @@ subroutine get_arguments(config, error)

if (config%isodens) then
config%qc_calc="tm"
inquire(file=config%database//"/isodens/"//config%sac_param_path, exist=ex)
inquire(file=config%database//"/isodens/"//config%sac_param_path, exist=ex)
if (ex) then
config%database=config%database//"/isodens"
else
Expand Down Expand Up @@ -570,7 +567,7 @@ subroutine get_arguments(config, error)
end if
end if
end if

if ((.not.(allocated(config%input))) .AND. (.not. (allocated(config%smd_solvent)))) then
if (.not.allocated(error)) then
call help(output_unit)
Expand All @@ -585,17 +582,17 @@ subroutine get_arguments(config, error)
end if
end if

end subroutine get_arguments
end subroutine get_arguments

!> Subroutine to Read the CPCM-SACMD Input File
subroutine read_input(config,error)
type(configuration_type) :: config
type(error_type), allocatable :: error

character(len=100) :: sac_param_path, smd_param_path, line
character(len=100) :: line

integer :: io_error, i, n,j, equal
logical :: ex, started
integer :: io_error, i, j, equal
logical :: ex

character(len=:), allocatable :: keyword, substring

Expand Down Expand Up @@ -637,7 +634,7 @@ subroutine read_input(config,error)
else
Call move_line(line(j:i-1),keyword)
end if

select case(keyword)
case ('TM','tm')
if (allocated(config%qc_calc)) then
Expand Down Expand Up @@ -690,7 +687,7 @@ subroutine read_input(config,error)
if (allocated(substring)) deallocate(substring)
j=i+1
end if
end do
end do

Read(input_unit,'(A)',iostat=io_error,err=255) line !Comment Line
Read(input_unit,'(A)',iostat=io_error,err=255) line
Expand All @@ -700,10 +697,10 @@ subroutine read_input(config,error)
Read(input_unit,*,iostat=io_error,err=255) line, config%probe
Call move_line(line,config%smd_solvent)
Read(input_unit,*,iostat=io_error,err=255) config%T
SysTemp=config%T
SysTemp=config%T
config%z1=0.995
config%z2=0.005

255 if (io_error .NE. 0) error stop "Check Input File."
end subroutine read_input

Expand All @@ -722,18 +719,15 @@ subroutine use_default(config, solv, home, error)
type(toml_error), allocatable :: config_error

character(len=:), allocatable, intent(in) :: home


type(toml_key), allocatable, dimension(:) :: list
integer :: stat
character(len=255) :: line
character(:), allocatable :: line2
logical :: ex
character(len=10) :: control, command
integer :: nconf, io

character(len=:), allocatable :: user

if (solv .eq. '') then
Call fatal_error(error,'The Solvent you specified is not available.')
return
Expand Down Expand Up @@ -761,10 +755,10 @@ subroutine use_default(config, solv, home, error)
if (ex) then
config%config_path="/home/"//user//"/cpcmx.toml"
else

inquire(file=home//"cpcmx.toml",exist=ex)

if (.not. ex) then
if (.not. ex) then
!call fatal_error(error, "No configuration found in "//home)
return
else
Expand All @@ -781,7 +775,7 @@ subroutine use_default(config, solv, home, error)
call config_table%get_keys(list)
do nconf=1,size(list)
select case(list(nconf)%key)
case("prog")
case("prog")
if (allocated(config%qc_calc)) cycle
call get_value(config_table,list(nconf),line2)
if (line2 .eq. "NONE") cycle
Expand Down Expand Up @@ -841,22 +835,22 @@ subroutine move_line(line,aline,hignore)

if (present(hignore)) then
if (.not. hignore) ignore=.false.
end if
end if

if (allocated(aline)) deallocate(aline)

if (ignore) then
do i= 1,len(trim(line))
if (line(i:i) .EQ. "#") then
if (line(i:i) .EQ. "#") then
allocate(character(len(trim(line(1:i-1)))) :: aline)
aline=trim(line(1:i-1))
exit
end if
end if
if (i .EQ. len(trim(line))) then
allocate(character(len(trim(line(1:i)))) :: aline)
aline=trim(line(1:i))
exit
end if
end if
end do
else
allocate(character(len(trim(line))) :: aline)
Expand Down Expand Up @@ -888,21 +882,21 @@ subroutine echo_init(config)
"Solvent:", config%smd_solvent, &
"Corresponding COSMO File:", config%csm_solvent

if (allocated(config%qc_calc)) then
if (allocated(config%qc_calc)) then
write(output_unit,'(5x,a,t35,a)') &
"QC Program:", config%qc_calc
else
write(output_unit,'(5x,a,t35,a)') &
"Solute COSMO File:", config%csm_solute
end if

end subroutine echo_init

subroutine check_error(error)
type(error_type), intent(in), allocatable :: error

integer :: point

if (allocated(error)) then
write(error_unit,'(a)') ""
point=index(error%message,".")
Expand Down
3 changes: 2 additions & 1 deletion src/cpcmx/data.f90
Original file line number Diff line number Diff line change
Expand Up @@ -467,8 +467,9 @@ end function density
function minnesota_eps(solvent,error) result(epsilon)
character(len=*), intent(in) :: solvent
type(error_type), allocatable :: error
real(wp):: epsilon
real(wp) :: epsilon

epsilon=ieee_value(epsilon,ieee_positive_inf)
select case(solvent_name(solvent))
case('infinity','inf')
epsilon=ieee_value(epsilon,ieee_positive_inf)
Expand Down
Loading

0 comments on commit 647105c

Please sign in to comment.