NECICore Subroutine

subroutine NECICore(iCacheFlag, tCPMD, tVASP, tMolpro_local, call_as_lib, int_name, filename_in, MemSize)

Arguments

Type IntentOptional Attributes Name
integer, intent(in), optional :: iCacheFlag
logical, intent(in), optional :: tCPMD
logical, intent(in), optional :: tVASP
logical, intent(in), optional :: tMolpro_local
logical, intent(in), optional :: call_as_lib
character(len=*), intent(in), optional :: int_name
character(len=*), intent(in), optional :: filename_in
integer(kind=int64), intent(in), optional :: MemSize

Contents

Source Code


Source Code

Subroutine NECICore(iCacheFlag, tCPMD, tVASP, tMolpro_local, call_as_lib, &
                    int_name, filename_in, MemSize)
    != NECICore is the main outline of the NECI Program.
    != It provides a route for calling NECI when accessed as a library, rather
    != than as a standalone program.
    != In:
    !=    iCacheFlag: controls the behaviour of the 4-index integral cache.
    !=                Currently relevant only for CPMD and VASP calculations.
    !=                iCacheFlag=0: initialise and destroy the cache.
    !=                iCacheFlag=1: initialise but don't destroy the cache.
    !=                iCacheFlag=2: reuse and destroy the cache.
    !=                iCacheFlag=3: reuse and keep the cache.
    !=    tCPMD: True if doing a CPMD-based calculation.
    !=    tVASP: True if doing a VASP-based calculation.
    !=    call_as_lib: True if called as subroutine from external code.
    !=    int_name: is the name of the integral file to read in if necessary
    !=    filename: is the name of the input file to read in if necessary
    !=    MemSize: Memory limit in MB

    use ReadInput_neci, only: ReadInputMain
    use SystemData, only: tMolpro, tMolproMimic, MolproID, called_as_lib
    use MemoryManager

    ! main-level modules.
    use Calc, only: CalcDoCalc
    use CalcData, only: tUseProcsAsNodes
    use kp_fciqmc_procs, only: kp_fciqmc_data
    use Parallel_neci, only: MPINodes, iProcIndex, &
                             neci_MPIInit_called, neci_MPINodes_called
    use read_fci, only: FCIDUMP_name

    use MPI_wrapper
    use UMatCache, only: UMat2D, tagUMat2D

    ! Utility modules.
    use global_utilities
    use constants
    use util_mod, only: get_free_unit

    USE MolproPlugin

    Implicit none
    integer, intent(in), optional :: iCacheFlag
    logical, intent(in), optional :: tCPMD, tVASP, tMolpro_local, call_as_lib
    character(*), intent(in), optional :: filename_in, int_name
    integer(int64), intent(in), optional :: MemSize
    type(timer), save :: proc_timer
    integer :: iunit, iunit2, i, j, isfreeunit, iCacheFlag_
    character(*), parameter :: this_routine = 'NECICore'
    character(:), allocatable :: Filename
    logical :: toverride_input, tFCIDUMP_exist, tCPMD_, tVASP_
    type(kp_fciqmc_data) :: kp
    interface
        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