Ford-modules part 11

This commit is contained in:
fabrizio22 2021-02-25 11:42:39 +01:00
parent 244657bc6e
commit c7b6b7f316
11 changed files with 129 additions and 109 deletions

View File

@ -8,14 +8,13 @@
!----------------------------------------------------------------------------
MODULE mp_global
!----------------------------------------------------------------------------
!
! ... Wrapper module, for compatibility. Contains a few "leftover" variables
! ... used for checks (all the *_file variables, read from data file),
! ... plus the routine mp_startup initializing MPI and the command line,
! ... plus the routine mp_global_end stopping MPI.
! ... Do not use this module to reference variables (e.g. communicators)
! ... belonging to each of the various parallelization levels:
! ... use the specific modules instead.
!! Wrapper module, for compatibility. Contains a few "leftover" variables
!! used for checks (all the *_file variables, read from data file),
!! plus the routine mp_startup initializing MPI and the command line,
!! plus the routine mp_global_end stopping MPI.
!! Do not use this module to reference variables (e.g. communicators)
!! belonging to each of the various parallelization levels:
!! use the specific modules instead.
! ... PLEASE DO NOT ADD NEW STUFF TO THIS MODULE. Removing stuff is ok.
!
USE mp_world, ONLY: world_comm, mp_world_start, mp_world_end
@ -44,16 +43,17 @@ CONTAINS
!-----------------------------------------------------------------------
SUBROUTINE mp_startup ( my_world_comm, start_images )
!-----------------------------------------------------------------------
! ... This wrapper subroutine initializes all parallelization levels.
! ... If option with_images=.true., processes are organized into images,
! ... each performing a quasi-indipendent calculation, such as a point
! .. in configuration space (NEB) or a phonon irrep (PHonon)
! ... Within each image processes are further subdivided into various
! ... groups and parallelization levels.
! ... IMPORTANT NOTICE 1: since the command line is read here, it may be
! ... convenient to call it in serial execution as well
! ... IMPORTANT NOTICE 2: most parallelization levels are initialized here
! ... but at least some will be moved to a later stage
!! This wrapper subroutine initializes all parallelization levels.
!! If option with_images=.true., processes are organized into images,
!! each performing a quasi-indipendent calculation, such as a point
!! in configuration space (NEB) or a phonon irrep (PHonon).
!! Within each image processes are further subdivided into various
!! groups and parallelization levels.
!
! IMPORTANT NOTICE 1: since the command line is read here, it may be
! convenient to call it in serial execution as well
! IMPORTANT NOTICE 2: most parallelization levels are initialized here
! but at least some will be moved to a later stage
!
USE command_line_options, ONLY : get_command_line, &
nimage_, npool_, nband_, ntg_, nyfft_

View File

@ -8,6 +8,9 @@
!----------------------------------------------------------------------------
MODULE mp_images
!----------------------------------------------------------------------------
!! Image groups (processors within an image). Images are used for
!! coarse-grid parallelization of semi-independent calculations,
!! e.g. points along the reaction path (NEB) or phonon irreps.
!
USE mp, ONLY : mp_barrier, mp_bcast, mp_size, mp_rank, mp_comm_split
USE io_global, ONLY : ionode, ionode_id
@ -16,26 +19,29 @@ MODULE mp_images
IMPLICIT NONE
SAVE
!
! ... Image groups (processors within an image). Images are used for
! ... coarse-grid parallelization of semi-independent calculations,
! ... e.g. points along the reaction path (NEB) or phonon irreps
INTEGER :: nimage = 1
!! number of images
INTEGER :: nproc_image=1
!! number of processors within an image
INTEGER :: me_image = 0
!! index of the processor within an image
INTEGER :: root_image= 0
!! index of the root processor within an image
INTEGER :: my_image_id=0
!! index of my image
INTEGER :: inter_image_comm = 0
!! inter image communicator
INTEGER :: intra_image_comm = 0
!! intra image communicator
!
INTEGER :: nimage = 1 ! number of images
INTEGER :: nproc_image=1 ! number of processors within an image
INTEGER :: me_image = 0 ! index of the processor within an image
INTEGER :: root_image= 0 ! index of the root processor within an image
INTEGER :: my_image_id=0 ! index of my image
INTEGER :: inter_image_comm = 0 ! inter image communicator
INTEGER :: intra_image_comm = 0 ! intra image communicator
CONTAINS
!
!-----------------------------------------------------------------------
SUBROUTINE mp_start_images ( nimage_, parent_comm )
!-----------------------------------------------------------------------
!
! ... Divide processors (of the "parent_comm" group) into "images".
! ... Requires: nimage_, read from command line
! ... parent_comm, typically world_comm = group of all processors
!! Divide processors (of the "parent_comm" group) into "images".
!! Requires: \(\text{nimage_}\), read from command line and
!! \(\text{parent_comm}\), typically world_comm = group of all processors
!
IMPLICIT NONE
INTEGER, INTENT(IN) :: nimage_, parent_comm
@ -96,7 +102,7 @@ CONTAINS
!
SUBROUTINE mp_init_image ( parent_comm )
!
! ... There is just one image: set it to the same as parent_comm (world)
!! There is just one image: set it to the same as parent_comm (world)
!
IMPLICIT NONE
INTEGER, INTENT(IN) :: parent_comm

View File

@ -11,13 +11,17 @@ MODULE parameters
IMPLICIT NONE
SAVE
INTEGER, PARAMETER :: &
npk = 40000, &! max number of k-points
ntypx = 10, &! max number of different types of atom
nsx = ntypx, &! max number of atomic species (CP)
natx = 50, &! max number of atoms for DFT+U+V calculations
sc_size = 1 ! Defines the supercell in DFT+U+V as composed by the unit cells located
! by (n1,n2,n3) in primitive vectors base with -sc_size <= ni <= sc_size,
! (2*sc_size+1)**3 is the number of cells
INTEGER, PARAMETER :: npk = 40000
!! max number of k-points
INTEGER, PARAMETER :: ntypx = 10
!! max number of different types of atom
INTEGER, PARAMETER :: nsx = ntypx
!! max number of atomic species (CP)
INTEGER, PARAMETER :: natx = 50
!! max number of atoms for DFT+U+V calculations
INTEGER, PARAMETER :: sc_size = 1
!! Defines the supercell in DFT+U+V as composed by the unit cells located
!! by (n1,n2,n3) in primitive vectors base with -sc_size <= ni <= sc_size,
!! \((2\text{sc_size}+1)^3\) is the number of cells.
END MODULE parameters

View File

@ -6,26 +6,6 @@
! or http://www.gnu.org/copyleft/gpl.txt .
!
!
! ... SUBROUTINE field_count: accepts two string (one of them is optional)
! and one integer and count the number of fields
! in the string separated by a blank or a tab
! character. If the optional string is specified
! (it has anyway len=1) it is assumed as the
! separator character.
! Ignores any character following the exclamation
! mark (fortran comment)
!
! ... SUBROUTINE con_cam: counts the number of fields in a string
! separated by the optional character
!
! ... SUBROUTINE field_compare: accepts two strings and one integer. Counts the
! fields contained in the first string and
! compares it with the integer.
! If they are less than the integer calls the
! routine error and show by the second string the
! name of the field where read-error occurred.
!
!
!----------------------------------------------------------------------------
MODULE parser
!----------------------------------------------------------------------------
@ -46,6 +26,11 @@ MODULE parser
!--------------------------------------------------------------------------
SUBROUTINE field_count( num, line, car )
!--------------------------------------------------------------------------
!! Accepts two string (one of them is optional) and one integer and count
!! the number of fields in the string separated by a blank or a tab
!! character. If the optional string is specified (it has anyway len=1)
!! it is assumed as the separator character.
!! Ignores any character following the exclamation mark (fortran comment).
!
IMPLICIT NONE
!
@ -168,6 +153,10 @@ MODULE parser
!--------------------------------------------------------------------------
SUBROUTINE field_compare( str, nf, var )
!--------------------------------------------------------------------------
!! Accepts two strings and one integer. Counts the fields contained in
!! the first string and compares it with the integer.
!! If they are less than the integer calls the routine error and show by
!! the second string the name of the field where read-error occurred.
!
IMPLICIT NONE
!
@ -190,6 +179,9 @@ MODULE parser
!--------------------------------------------------------------------------
SUBROUTINE con_cam(num, line, car)
!--------------------------------------------------------------------------
!! Counts the number of fields in a string separated by the optional
!! character.
!
CHARACTER(LEN=*) :: line
CHARACTER(LEN=1) :: sep
CHARACTER(LEN=1), OPTIONAL :: car
@ -226,7 +218,8 @@ MODULE parser
!--------------------------------------------------------------------------
SUBROUTINE get_field(n, field, str, sep)
!--------------------------------------------------------------------------
! Extract whitespace-separated nth block from string
!! Extract whitespace-separated n-th block from string.
!
IMPLICIT NONE
INTEGER,INTENT(IN) :: n
CHARACTER(len=*),INTENT(OUT) :: field

View File

@ -9,24 +9,25 @@
!------------------------------------------------------------------------
SUBROUTINE setdqf( nqf, qfcoef, mesh, r, l, drho )
!-----------------------------------------------------------------------
!
! ... Computes the derivative of the Q function, dQ/dr,
! ... from its polynomial expansion (valid for r < rinner)
! ... On input: nqf = number of polynomial coefficients
! ... qfcoef(nqf)= the coefficients defining Q
! ... mesh = number of mesh point
! ... r(mesh)= the radial mesh
! ... l = angular momentum
! ... On output:
! ... drho(mesh)= dQ(r)/dr
!! Computes the derivative of the Q function, \(dQ/dr\), from its
!! polynomial expansion (valid for r < rinner).
!
USE kinds, ONLY: dp
!
IMPLICIT NONE
!
INTEGER, INTENT(in):: nqf, l, mesh
REAL(dp), INTENT(in) :: r(mesh), qfcoef(nqf)
INTEGER, INTENT(in):: nqf
!! number of polynomial coefficients
INTEGER, INTENT(in) :: l
!! angular momentum
INTEGER, INTENT(in) :: mesh
!! number of mesh point
REAL(dp), INTENT(in) :: r(mesh)
!! the radial mesh
REAL(dp), INTENT(in) :: qfcoef(nqf)
!! the coefficients defining Q
REAL(dp), INTENT(out) :: drho(mesh)
!! \(dQ(r)/dr\)
!
INTEGER :: ir, i
!

View File

@ -7,7 +7,7 @@
!
LOGICAL FUNCTION test_input_xml (myunit)
!
! check if file opened as unit "myunit" is a xml file or not
!! Check if file opened as unit "myunit" is a xml file or not.
!
IMPLICIT NONE
!

View File

@ -12,7 +12,7 @@
!
MODULE wannier_gw
!
! ... The variables needed for gww-gwl code (head.x)
!! The variables needed for gww-gwl code (head.x)
!
USE kinds, ONLY: DP
!

View File

@ -9,31 +9,41 @@
MODULE wannier_new
!
! ... Variables to construct and store wannier functions
!! Variables to construct and store wannier functions
!
USE kinds, ONLY : DP
!
SAVE
!
INTEGER, PARAMETER :: ningx = 10 ! max number of trial wavefunction ingredients
INTEGER, PARAMETER :: ningx = 10
!! max number of trial wavefunction ingredients
LOGICAL :: &
use_wannier, &! if .TRUE. wannier functions are constructed
rkmesh, &! if .TRUE. regular k-mesh without symmetry is used !now used in input_parameters_mod
plot_wannier, &! if .TRUE. wannier number plot_wan_num is plotted
use_energy_int, &! if .TRUE. uses energy interval for wannier generation, not band numbers
print_wannier_coeff ! if .TRUE. computes and prints coefficients of wannier decomp. on atomic functions
INTEGER :: &
nwan, &! number of wannier functions
plot_wan_num, &! number of wannier for plotting
plot_wan_spin ! spin of wannier for plotting
REAL(kind=DP), allocatable :: &
wan_pot(:,:), &! constrained potential
wannier_energy(:,:), &! energy of each wannier (of each spin)
wannier_occ(:,:,:) ! occupation matrix of wannier functions(of each spin)
COMPLEX(kind=DP), allocatable :: &
pp(:,:), &! <phi|S|psi> projections
coef(:,:,:) ! coefficients of wannier decomp. on atomic functions
LOGICAL :: use_wannier
!! if .TRUE. wannier functions are constructed
LOGICAL :: rkmesh
!! if .TRUE. regular k-mesh without symmetry is used !now used in input_parameters_mod
LOGICAL :: plot_wannier
!! if .TRUE. wannier number plot_wan_num is plotted
LOGICAL :: use_energy_int
!! if .TRUE. uses energy interval for wannier generation, not band numbers
LOGICAL :: print_wannier_coeff
!! if .TRUE. computes and prints coefficients of wannier decomp. on atomic functions
INTEGER :: nwan
!! number of wannier functions
INTEGER :: plot_wan_num
!! number of wannier for plotting
INTEGER :: plot_wan_spin
!! spin of wannier for plotting
REAL(kind=DP), allocatable :: wan_pot(:,:)
!! constrained potential
REAL(kind=DP), allocatable :: wannier_energy(:,:)
!! energy of each wannier (of each spin)
REAL(kind=DP), allocatable :: wannier_occ(:,:,:)
!! occupation matrix of wannier functions(of each spin)
COMPLEX(kind=DP), allocatable :: pp(:,:)
!! <phi|S|psi> projections
COMPLEX(kind=DP), allocatable :: coef(:,:,:)
!! coefficients of wannier decomp. on atomic functions
TYPE ingredient
INTEGER :: l = 0, & ! l value for atomic wfc

View File

@ -11,7 +11,7 @@ MODULE wrappers
!! This module contains fortran wrappers to POSIX system calls.
!! The wrappers are used to convert the Fortran CHARACTER array to
!! null-terminated C *char. The conversion and the interface is done
!! with the F95 intrinsic \(\texttt{iso_c_binding module}\).
!! with the F95 intrinsic \(\texttt{iso_c_binding}\) module.
!! Additionally, it provides interfaces to the C functions in clib/:
!! \(\texttt{eval_infix, md5_from_file, f_mkdir_safe}\)
!

View File

@ -6,6 +6,11 @@
! or http://www.gnu.org/copyleft/gpl.txt .
!
MODULE wy_pos
!! Main subroutine: \(\texttt{wypos}\). Converts atomic positions
!! given in Wyckoff convention: multiplicity-letter + parameter(s),
!! to crystal positions.
USE kinds, ONLY : DP
IMPLICIT NONE
@ -17,18 +22,16 @@ PUBLIC wypos
CONTAINS
SUBROUTINE wypos(tau,wp,inp,space_group_number,uniqueb,&
rhombohedral,origin_choice)
!-----------------------------------------------------------
! Convert atomic positions given in Wyckoff convention:
! multiplicity-letter + parameter(s), to crystal positions
! wp = Wyckoff label (e.g. 8c)
! inp(3) = parameter(s) (if needed)
!! Convert atomic positions given in Wyckoff convention:
!! multiplicity-letter + parameter(s), to crystal positions.
!-----------------------------------------------------------
REAL(DP), DIMENSION(3), INTENT(OUT) :: tau
REAL(DP), INTENT(IN) :: inp(3)
!! parameter(s) (if needed)
CHARACTER(LEN=*), INTENT (IN) :: wp
!! Wyckoff label (e.g. 8c)
INTEGER, INTENT(IN) :: space_group_number
LOGICAL, INTENT(IN) :: uniqueb, rhombohedral
INTEGER, INTENT(IN) :: origin_choice

View File

@ -8,10 +8,11 @@
! This file holds XSF (=Xcrysden Structure File) utilities.
! Routines written by Tone Kokalj on Mon Jan 27 18:51:17 CET 2003
!
! -------------------------------------------------------------------
! this routine writes the crystal structure in XSF format
! -------------------------------------------------------------------
!-------------------------------------------------------------------
SUBROUTINE xsf_struct (alat, at, nat, tau, atm, ityp, ounit)
!-------------------------------------------------------------------
!! This routine writes the crystal structure in XSF format.
!
USE kinds, ONLY : DP
USE constants, ONLY : BOHR_RADIUS_ANGS
IMPLICIT NONE
@ -46,12 +47,14 @@ END SUBROUTINE xsf_struct
! -------------------------------------------------------------------
! this routine writes the 3D scalar field (i.e. uniform mesh of points)
! in XSF format using the FFT mesh (i.e. fast write)
! -------------------------------------------------------------------
!-------------------------------------------------------------------
SUBROUTINE xsf_fast_datagrid_3d &
(rho, nr1, nr2, nr3, nr1x, nr2x, nr3x, at, alat, ounit)
!-------------------------------------------------------------------
!! This routine writes the 3D scalar field (i.e. uniform mesh of points)
!! in XSF format using the FFT mesh (i.e. fast write).
!
USE kinds, ONLY : DP
USE constants, ONLY : BOHR_RADIUS_ANGS
IMPLICIT NONE