subroutine NECICodeInit(tCPMD, tVASP, called_as_lib, MemSize)
import :: dp, int64
implicit none
logical, intent(in) :: tCPMD, tVASP, called_as_lib
integer(int64), intent(in), optional :: MemSize
end subroutine
end interface
def_default(iCacheFlag_, iCacheFlag, 0)
def_default(tCPMD_, tCPMD, .false.)
def_default(tVASP_, tVASP, .false.)
def_default(tMolpro, tMolpro_local, .false.)
def_default(called_as_lib, call_as_lib, .false.)
def_default(FCIDUMP_name, int_name, 'FCIDUMP')
def_default(filename, filename_in, '')
#ifdef SX
call stop_all(this_routine, 'The NEC compiler does not produce a working &
&version of NECI.')
#endif
neci_MPIInit_called = .false.
neci_MPINodes_called = .false.
! Do the program initialisation.
call NECICodeInit(tCPMD_, tVASP_, called_as_lib, MemSize)
proc_timer%timer_name = 'NECICUBE '
call set_timer(proc_timer)
! See ReadInputMain. Causes the command line arguments to be checked for the input filename.
toverride_input = .false.
if (tMolpro) then
IF (molpro_plugin) THEN
FCIDUMP_name = TRIM(molpro_plugin_fcidumpname)
ELSE
FCIDUMP_name = adjustl(int_name)
END IF
inquire (file="FCIQMC_input_override", exist=toverride_input)
if (toverride_input) then
Filename = "FCIQMC_input_override"
else
IF (molpro_plugin) THEN
filename = TRIM(molpro_plugin_datafilename)
ELSE
filename = filename_in
end if
MolproID = ''
if (iProcIndex == Root) then
!Now, extract the unique identifier for the input file that is read in.
#ifdef old_and_buggy
i = 14
j = 1
do while (filename(i:i) /= ' ')
MolproID(j:j) = filename(i:i)
i = i + 1
j = j + 1
end do
#else
i = INDEX(filename, '/', .TRUE.) + 1
j = INDEX(filename(i:), 'NECI'); IF (j /= 0) i = i + j - 1
MolproID = filename(i:MIN(i + LEN(MolproID) - 1, LEN(filename)))
#endif
write(stdout, "(A,A)") "Molpro unique filename suffix: ", MolproID
end if
end if
end if
if (.not. (tCPMD_ .or. tVASP_)) then
! CPMD and VASP calculations call the input parser *before* they call
! NECICore. This is to allow the NECI input filename(s) to be specified
! easily from within the CPMD/VASP input files.
call ReadInputMain(Filename, toverride_input, kp)
end if
call MPINodes(tUseProcsAsNodes) ! Setup MPI Node information - this is dependent upon knowing the job type configurations.
call NECICalcInit(iCacheFlag_)
! Actually do the calculations we're meant to. :-)
call CalcDoCalc(kp)
! And all done: pick up after ourselves and settle down for a cup of tea.
call NECICalcEnd(iCacheFlag_)
call halt_timer(proc_timer)
if (tMolpro .and. (.not. toverride_input) .and. (.not. tMolproMimic)) then
!Delete the FCIDUMP unless we are overriding the input, or mimicing molpro run-time behaviour
if (iProcIndex == 0) then
inquire (file='FCIDUMP', exist=tFCIDUMP_exist)
if (tFCIDUMP_exist) then
iunit = get_free_unit()
open(iunit, file=FCIDUMP_name, status='old', form='formatted')
close(iunit)
!close(iunit,status='delete')
end if
end if
end if
call NECICodeEnd(tCPMD_, tVASP_)
return
End Subroutine NECICore
subroutine NECICodeInit(tCPMD, tVASP, call_as_lib, MemSize)
use MolproPlugin
!= Initialise the NECI code. This contains all the initialisation
!= procedures for the code (as opposed to the system in general): e.g. for
!= the memory handling scheme, the timing routines, any parallel routines etc.
!= In:
!= tCPMD: True if doing a CPMD-based calculation.
!= tVASP: True if doing a VASP-based calculation.
! Utility modules
use MemoryManager, only: InitMemoryManager
use timing_neci, only: time_at_all, init_timing
use Parallel_neci, only: MPIInit
use SystemData, only: tMolpro
use CalcData, only: s_global_start
use constants, only: dp, int64
use util_mod, only: neci_etime
implicit none
logical, intent(in) :: tCPMD, tVASP, call_as_lib
integer(int64), intent(in), optional :: MemSize
real(dp) :: tend(2)
time_at_all = .not. call_as_lib
! MPIInit contains dummy initialisation for serial jobs, e.g. so we
! can refer to the processor index being 0 for the parent processor.
Call MPIInit(tCPMD .or. tVASP .or. tMolpro .or. call_as_lib) ! CPMD and VASP have their own MPI initialisation and termination routines.
! Measure when NECICore is called. We need to do this here, as molcas
! and molpro can call NECI part way through a run, so it is no use to time
! from when the _process_ began.
! As this can use MPI_WTIME, we can only call this after the MPIInit call
s_global_start = neci_etime(tend)
! find out whether this is a Molpro plugin
CALL MolproPluginInit(tMolpro)
! end find out whether this is a Molpro plugin
! If we use MPI_WTIME for timing, we have to call MPIInit first
call init_timing()
if (.not. TCPMD) then
call InitMemoryManager(MemSize)
end if
call environment_report(tCPMD)
end subroutine NECICodeInit