main.f90 Source File

Source Code


Source Code

#include "precompilerdefinitions"
program atomic_distribution
!!{!src/atomic_distribution/manual.md!}
use konstanter, only: flyt
use type_crystalstructure, only: lo_crystalstructure
use type_mdsim, only: lo_mdsim
use type_symmetrylist, only: lo_symlist
use helpers, only: lo_mpi_helper
use options, only: lo_opts

use pairmapping
use vectordist
use pair_distribution
use mean_square_displacement
use timedistance_correlation
use correlationfunction
implicit none
!
type(lo_opts) :: opts
type(lo_crystalstructure) :: uc,ss
type(lo_mdsim) :: sim
type(lo_symlist) :: sl
type(lo_vectordist) :: vd
type(lo_pairmapping) :: pm
type(lo_pair_distribution) :: pdf
type(lo_mean_square_displacement) :: msd
type(lo_mpi_helper) :: mw
!type(lo_timedistance_correlation) :: tdc

! get command line arguments
call opts%parse()
call mw%init()
! read positions
call uc%readfromfile('infile.ucposcar')
write(*,*) '... read unitcell'
call ss%readfromfile('infile.ssposcar')
write(*,*) '... read supercell'

! Get all kinds of symmetry stuff
if ( opts%cutoff .lt. 0.0_flyt ) then
    opts%cutoff=ss%maxcutoff()
endif

! Get the pair symmetry stuff
call sl%generate(uc,ss,opts%cutoff,-1.0_flyt,-1.0_flyt,transposition=.false.,firstorder=.true.,polar=.false.)
 
! write(*,*) '... found '//tochar(sy%nun)//' unique atoms'
! do i=1,sy%nun
!     write(*,*) '    atom ',i,uc%atomic_symbol( uc%species(sy%un(i)%atom_in_uc) )
! enddo
 
! I know the number of unique atoms, and coordination shells. I need a reverse list, sort of.
! I need to know for each atom in the unit cell, and for each pair, which atoms to sum over 
! and how they should transform
call pm%setup_symmetry(sl,uc,ss)
 
! Also need the actual simulation
call sim%read_from_file(verbosity=2,stride=opts%stride)

! First we calculate the symmetry-projected radial pair distribution function
call pdf%bin(ss,pm,sim,opts%nbin)
! Write this to file
call pdf%write_to_hdf5()
write(*,*) 'Wrote pair distribution function to file'

! Then we calculate the mean square displacement, could be useful
call msd%generate(ss,pm,sim)
call msd%write_to_hdf5()
call msd%write_to_plaintext(pm,uc)
write(*,*) 'Wrote mean square displacement to file'

! ! Additionally, I like the time-distance correlation functions. Not exactly sure what they 
! ! are good for, but it's interesting to look at. Only in the non-diffusive case for now.
! if ( opts%timedistance ) then
!     if ( pdf%diffusion .eqv. .false. ) then
!         call tdc%generate(pdf,uc,ss,pm,sim,opts%nbin)
!         call tdc%write_to_hdf5()
!     endif
! endif

! generate the vector distribution (only in case of no diffusion, this makes little sense if things are melted)
if ( pdf%diffusion .eqv. .false. ) then
    call vd%generate(pm,sim,opts%bintype,opts%transform,opts%nbin)
    call vd%write_to_hdf5(pm)
else
    ! if it's melted, go with the probability density instead!
    write(*,*) 'Probability density function, but not yet. Nag on me to fix this.'
    call mw%destroy()
    stop
endif

! So I decided to comment it instead of writing the manual.
! realspace velocity-velocity autocorrelation functions
! call cf%generate(uc,ss,pm,sim)
! call cf%write_to_plaintext(pm,uc)

write(*,*) 'All done!'
call mw%destroy()

end program