Skip to content

Commit

Permalink
Small presentational change: programs now report Fortran/Python/NumPy…
Browse files Browse the repository at this point in the history
… version numbers
  • Loading branch information
Michael-P-Allen committed Aug 22, 2024
1 parent 3ec8d43 commit 1fcc4b5
Show file tree
Hide file tree
Showing 98 changed files with 756 additions and 245 deletions.
14 changes: 11 additions & 3 deletions adjust.f90
Original file line number Diff line number Diff line change
Expand Up @@ -36,9 +36,11 @@ PROGRAM adjust
! There is nothing here specific to Lennard-Jones
! We assume unit mass and adjust only the translational kinetic energy

USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor
USE config_io_module, ONLY : read_cnf_atoms, read_cnf_mols, write_cnf_atoms, write_cnf_mols
USE maths_module, ONLY : lowercase
USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor, &
& COMPILER_VERSION, COMPILER_OPTIONS

USE config_io_module, ONLY : read_cnf_atoms, read_cnf_mols, write_cnf_atoms, write_cnf_mols
USE maths_module, ONLY : lowercase

IMPLICIT NONE

Expand Down Expand Up @@ -68,6 +70,12 @@ PROGRAM adjust

NAMELIST /nml/ delta_rho, delta_kin, velocities, molecules

WRITE ( unit=output_unit, fmt='(a)' ) 'adjust'
WRITE ( unit=output_unit, fmt='(2a)' ) 'Compiler: ', COMPILER_VERSION()
WRITE ( unit=output_unit, fmt='(2a/)' ) 'Options: ', COMPILER_OPTIONS()

WRITE ( unit=output_unit, fmt='(a)' ) 'Adjusts kinetic energy and/or density of configuration'

! Set default parameters
velocities = .FALSE. ! By default, assume MC configuration
molecules = 'atom' ! Options are 'atom', 'chain', 'linear', 'nonlinear'
Expand Down
2 changes: 1 addition & 1 deletion averages_module.f90
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ MODULE averages_module
! the software, you should not imply endorsement by the authors or publishers. !
!------------------------------------------------------------------------------------------------!

USE, INTRINSIC :: iso_fortran_env, ONLY : output_unit, error_unit, iostat_end, iostat_eor
USE, INTRINSIC :: iso_fortran_env, ONLY : output_unit, error_unit

IMPLICIT NONE
PRIVATE
Expand Down
8 changes: 6 additions & 2 deletions bd_nvt_lj.f90
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,8 @@ PROGRAM bd_nvt_lj
! Despite the program name, there is nothing here specific to Lennard-Jones
! The model is defined in md_module

USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor
USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor, &
& COMPILER_VERSION, COMPILER_OPTIONS

USE config_io_module, ONLY : read_cnf_atoms, write_cnf_atoms
USE averages_module, ONLY : run_begin, run_end, blk_begin, blk_end, blk_add
Expand Down Expand Up @@ -72,7 +73,10 @@ PROGRAM bd_nvt_lj

NAMELIST /nml/ nblock, nstep, r_cut, dt, gamma, temperature

WRITE ( unit=output_unit, fmt='(a)' ) 'bd_nvt_lj'
WRITE ( unit=output_unit, fmt='(a)' ) 'bd_nvt_lj'
WRITE ( unit=output_unit, fmt='(2a)' ) 'Compiler: ', COMPILER_VERSION()
WRITE ( unit=output_unit, fmt='(2a/)' ) 'Options: ', COMPILER_OPTIONS()

WRITE ( unit=output_unit, fmt='(a)' ) 'Brownian dynamics, constant-NVT ensemble'
WRITE ( unit=output_unit, fmt='(a)' ) 'Particle mass m=1 throughout'
CALL introduction
Expand Down
12 changes: 10 additions & 2 deletions cluster.f90
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,10 @@ PROGRAM cluster
! Reference: SD Stoddard J Comp Phys, 27, 291 (1978)
! This simple algorithm does not scale well to large N

USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor
USE config_io_module, ONLY : read_cnf_atoms
USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor, &
& COMPILER_VERSION, COMPILER_OPTIONS

USE config_io_module, ONLY : read_cnf_atoms

IMPLICIT NONE

Expand All @@ -53,6 +55,12 @@ PROGRAM cluster

NAMELIST /nml/ r_cl

WRITE ( unit=output_unit, fmt='(a)' ) 'cluster'
WRITE ( unit=output_unit, fmt='(2a)' ) 'Compiler: ', COMPILER_VERSION()
WRITE ( unit=output_unit, fmt='(2a/)' ) 'Options: ', COMPILER_OPTIONS()

WRITE ( unit=output_unit, fmt='(a)' ) 'Identifies clusters in configuration'

r_cl = 1.5 ! default value

READ ( unit=input_unit, nml=nml, iostat=ioerr ) ! namelist input
Expand Down
2 changes: 1 addition & 1 deletion config_io_module.f90
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ MODULE config_io_module
!------------------------------------------------------------------------------------------------!

USE, INTRINSIC :: iso_fortran_env, ONLY : error_unit, iostat_end, iostat_eor

IMPLICIT NONE
PRIVATE

Expand Down
11 changes: 8 additions & 3 deletions corfun.f90
Original file line number Diff line number Diff line change
Expand Up @@ -39,9 +39,11 @@ PROGRAM corfun
! Advantage can be taken of the fact that the data is real, but for clarity
! we just use the complex FFT with imaginary parts of the data set to zero

USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor
USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor, &
& COMPILER_VERSION, COMPILER_OPTIONS
USE, INTRINSIC :: iso_c_binding
USE maths_module, ONLY : random_normal, expm1

USE maths_module, ONLY : random_normal, expm1

IMPLICIT NONE
INCLUDE 'fftw3.f03'
Expand Down Expand Up @@ -80,7 +82,10 @@ PROGRAM corfun

NAMELIST /nml/ nt, origin_interval, nstep, nequil, delta, temperature

WRITE( unit=output_unit, fmt='(a)' ) 'corfun'
WRITE ( unit=output_unit, fmt='(a)' ) 'corfun'
WRITE ( unit=output_unit, fmt='(2a)' ) 'Compiler: ', COMPILER_VERSION()
WRITE ( unit=output_unit, fmt='(2a/)' ) 'Options: ', COMPILER_OPTIONS()

WRITE( unit=output_unit, fmt='(a)' ) 'Illustrates methods for calculating time correlation functions'
WRITE( unit=output_unit, fmt='(a)' ) 'using synthetic data from a generalized Langevin equation'

Expand Down
12 changes: 10 additions & 2 deletions diffusion.f90
Original file line number Diff line number Diff line change
Expand Up @@ -48,8 +48,10 @@ PROGRAM diffusion
! Although a default value of delta=0.05 is supplied, it is really only a place-holder
! for the correct user-supplied value (time interval between configurations)

USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor
USE config_io_module, ONLY : read_cnf_atoms
USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor, &
& COMPILER_VERSION, COMPILER_OPTIONS

USE config_io_module, ONLY : read_cnf_atoms

IMPLICIT NONE

Expand Down Expand Up @@ -80,6 +82,12 @@ PROGRAM diffusion

NAMELIST /nml/ nt, origin_interval, delta

WRITE ( unit=output_unit, fmt='(a)' ) 'diffusion'
WRITE ( unit=output_unit, fmt='(2a)' ) 'Compiler: ', COMPILER_VERSION()
WRITE ( unit=output_unit, fmt='(2a/)' ) 'Options: ', COMPILER_OPTIONS()

WRITE ( unit=output_unit, fmt='(a)' ) 'Calculates diffusion correlations from sequence of configurations'

! Example default values
nt = 500 ! Max correlation time (as a multiple of interval between configurations)
origin_interval = 10 ! We only take time origins at these intervals, for efficiency
Expand Down
13 changes: 9 additions & 4 deletions diffusion_test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -38,9 +38,11 @@ PROGRAM diffusion_test
! are given in simulation units defined by the model
! We assume mass m=1 throughout

USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor
USE config_io_module, ONLY : write_cnf_atoms
USE maths_module, ONLY : random_normals
USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor, &
& COMPILER_VERSION, COMPILER_OPTIONS

USE config_io_module, ONLY : write_cnf_atoms
USE maths_module, ONLY : random_normals

IMPLICIT NONE

Expand All @@ -62,7 +64,10 @@ PROGRAM diffusion_test

NAMELIST /nml/ n, nblock, nstep, dt, gamma, temperature, box

WRITE ( unit=output_unit, fmt='(a)' ) 'diffusion_test'
WRITE ( unit=output_unit, fmt='(a)' ) 'diffusion_test'
WRITE ( unit=output_unit, fmt='(2a)' ) 'Compiler: ', COMPILER_VERSION()
WRITE ( unit=output_unit, fmt='(2a/)' ) 'Options: ', COMPILER_OPTIONS()

WRITE ( unit=output_unit, fmt='(a)' ) 'Brownian dynamics without interactions, constant-NVT ensemble'
WRITE ( unit=output_unit, fmt='(a)' ) 'Particle mass m=1 throughout'

Expand Down
19 changes: 12 additions & 7 deletions dpd.f90
Original file line number Diff line number Diff line change
Expand Up @@ -45,12 +45,14 @@ PROGRAM dpd
! We recommend a somewhat smaller timestep than their 0.04.
! They also give an approximate expression for the pressure, written out at the end for comparison

USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor
USE config_io_module, ONLY : read_cnf_atoms, write_cnf_atoms
USE averages_module, ONLY : run_begin, run_end, blk_begin, blk_end, blk_add
USE maths_module, ONLY : lowercase
USE dpd_module, ONLY : introduction, conclusion, allocate_arrays, deallocate_arrays, &
& force, lowe, shardlow, p_approx, r, v, f, n, potential_type
USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor, &
& COMPILER_VERSION, COMPILER_OPTIONS

USE config_io_module, ONLY : read_cnf_atoms, write_cnf_atoms
USE averages_module, ONLY : run_begin, run_end, blk_begin, blk_end, blk_add
USE maths_module, ONLY : lowercase
USE dpd_module, ONLY : introduction, conclusion, allocate_arrays, deallocate_arrays, &
& force, lowe, shardlow, p_approx, r, v, f, n, potential_type

IMPLICIT NONE

Expand Down Expand Up @@ -78,7 +80,10 @@ PROGRAM dpd

NAMELIST /nml/ nblock, nstep, dt, temperature, a, gamma, method

WRITE ( unit=output_unit, fmt='(a)' ) 'dpd'
WRITE ( unit=output_unit, fmt='(a)' ) 'dpd'
WRITE ( unit=output_unit, fmt='(2a)' ) 'Compiler: ', COMPILER_VERSION()
WRITE ( unit=output_unit, fmt='(2a/)' ) 'Options: ', COMPILER_OPTIONS()

WRITE ( unit=output_unit, fmt='(a)' ) 'Dissipative particle dynamics, constant-NVT ensemble'
WRITE ( unit=output_unit, fmt='(a)' ) 'Particle mass=1 and cutoff=1 throughout'
CALL introduction
Expand Down
9 changes: 8 additions & 1 deletion eos_hs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,8 @@ PROGRAM eos_hs
! That paper also gives references to previous approximate equations of state (such as the
! venerable Carnahan-Starling equation).

USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor
USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor, &
& COMPILER_VERSION, COMPILER_OPTIONS

USE maths_module, ONLY : polyval

Expand All @@ -47,6 +48,12 @@ PROGRAM eos_hs

NAMELIST /nml/ density

WRITE ( unit=output_unit, fmt='(a)' ) 'eos_hs'
WRITE ( unit=output_unit, fmt='(2a)' ) 'Compiler: ', COMPILER_VERSION()
WRITE ( unit=output_unit, fmt='(2a/)' ) 'Options: ', COMPILER_OPTIONS()

WRITE ( unit=output_unit, fmt='(a)' ) 'Approximate hard sphere pressure at given density'

! Set sensible default values
density = 0.75

Expand Down
14 changes: 11 additions & 3 deletions eos_lj.f90
Original file line number Diff line number Diff line change
Expand Up @@ -35,9 +35,11 @@ PROGRAM eos_lj
! Formulae for P, E/N etc in terms of the scaled free energy derivatives a_res(0,1) etc
! may be found in the above papers

USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor
USE lrc_module, ONLY : potential_lrc, pressure_lrc, pressure_delta
USE eos_lj_module, ONLY : a_res_full, a_res_cutshift
USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor, &
& COMPILER_VERSION, COMPILER_OPTIONS

USE lrc_module, ONLY : potential_lrc, pressure_lrc, pressure_delta
USE eos_lj_module, ONLY : a_res_full, a_res_cutshift

IMPLICIT NONE

Expand All @@ -50,6 +52,12 @@ PROGRAM eos_lj

NAMELIST /nml/ temperature, density

WRITE ( unit=output_unit, fmt='(a)' ) 'eos_lj'
WRITE ( unit=output_unit, fmt='(2a)' ) 'Compiler: ', COMPILER_VERSION()
WRITE ( unit=output_unit, fmt='(2a/)' ) 'Options: ', COMPILER_OPTIONS()

WRITE ( unit=output_unit, fmt='(a)' ) 'Approximate Lennard-Jones EOS data at given density, temperature'

! Set sensible default values
temperature = 1.0
density = 0.75
Expand Down
12 changes: 10 additions & 2 deletions error_calc.f90
Original file line number Diff line number Diff line change
Expand Up @@ -31,8 +31,10 @@ PROGRAM error_calc
! See G Ciccotti and JP Ryckaert Mol Phys 40 141 (1980)
! and AD Baczewski and SD Bond J Chem Phys 139 044107 (2013)

USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor
USE maths_module, ONLY : random_normal, expm1
USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor, &
& COMPILER_VERSION, COMPILER_OPTIONS

USE maths_module, ONLY : random_normal, expm1

IMPLICIT NONE

Expand All @@ -53,6 +55,12 @@ PROGRAM error_calc

NAMELIST /nml/ nstep, nequil, n_repeat, delta, variance, average

WRITE ( unit=output_unit, fmt='(a)' ) 'error_calc'
WRITE ( unit=output_unit, fmt='(2a)' ) 'Compiler: ', COMPILER_VERSION()
WRITE ( unit=output_unit, fmt='(2a/)' ) 'Options: ', COMPILER_OPTIONS()

WRITE ( unit=output_unit, fmt='(a)' ) 'Error estimation in average of correlated synthetic data series'

! Example default values
nstep = 2**16 ! Number of steps, about 60,000 for example
nequil = 10000 ! Number of equilibration timesteps
Expand Down
14 changes: 11 additions & 3 deletions ewald.f90
Original file line number Diff line number Diff line change
Expand Up @@ -32,9 +32,11 @@ PROGRAM ewald
! Compares with brute force summation in real space over shells of periodic boxes
! Leave namelist empty to accept supplied defaults

USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor
USE config_io_module, ONLY : read_cnf_atoms
USE ewald_module, ONLY : pot_r_ewald, pot_k_ewald, pot_k_pm_ewald
USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor, &
& COMPILER_VERSION, COMPILER_OPTIONS

USE config_io_module, ONLY : read_cnf_atoms
USE ewald_module, ONLY : pot_r_ewald, pot_k_ewald, pot_k_pm_ewald

IMPLICIT NONE

Expand All @@ -52,6 +54,12 @@ PROGRAM ewald

NAMELIST /nml/ kappa, nk, nbox

WRITE ( unit=output_unit, fmt='(a)' ) 'ewald'
WRITE ( unit=output_unit, fmt='(2a)' ) 'Compiler: ', COMPILER_VERSION()
WRITE ( unit=output_unit, fmt='(2a/)' ) 'Options: ', COMPILER_OPTIONS()

WRITE ( unit=output_unit, fmt='(a)' ) 'Energy of system of charges by Ewald summation'

! Sensible default values
kappa = 6.0
nk = 8
Expand Down
9 changes: 8 additions & 1 deletion fft3dwrap.f90
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,8 @@ PROGRAM fft3dwrap
! We assume that compiler flags are set such that real and integer Fortran variables
! have the appropriate precision to match their C counterparts

USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor
USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor, &
& COMPILER_VERSION, COMPILER_OPTIONS
USE, INTRINSIC :: iso_c_binding

IMPLICIT NONE
Expand All @@ -56,6 +57,12 @@ PROGRAM fft3dwrap

NAMELIST /nml/ sc2, box

WRITE ( unit=output_unit, fmt='(a)' ) 'fft3dwrap'
WRITE ( unit=output_unit, fmt='(2a)' ) 'Compiler: ', COMPILER_VERSION()
WRITE ( unit=output_unit, fmt='(2a/)' ) 'Options: ', COMPILER_OPTIONS()

WRITE ( unit=output_unit, fmt='(a)' ) 'Illustrates calling of functions from FFTW library'

! Set sensible default values for testing
sc2 = 2**6 ! Not essential to be a power of 2, but usually more efficient
box = 6.0 ! Large enough to accommodate the chosen 3D Gaussian, for good comparison with analytical result
Expand Down
14 changes: 11 additions & 3 deletions grint.f90
Original file line number Diff line number Diff line change
Expand Up @@ -49,9 +49,11 @@ PROGRAM grint

! Values of basic parameters are read from standard input using a namelist nml

USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor
USE config_io_module, ONLY : read_cnf_atoms
USE grint_module, ONLY : fit
USE, INTRINSIC :: iso_fortran_env, ONLY : input_unit, output_unit, error_unit, iostat_end, iostat_eor, &
& COMPILER_VERSION, COMPILER_OPTIONS

USE config_io_module, ONLY : read_cnf_atoms
USE grint_module, ONLY : fit

IMPLICIT NONE

Expand Down Expand Up @@ -95,6 +97,12 @@ PROGRAM grint

NAMELIST /nml/ dz, dr, z_mid, nz, nc, nr, zskip, cskip, iz_max

WRITE ( unit=output_unit, fmt='(a)' ) 'grint'
WRITE ( unit=output_unit, fmt='(2a)' ) 'Compiler: ', COMPILER_VERSION()
WRITE ( unit=output_unit, fmt='(2a/)' ) 'Options: ', COMPILER_OPTIONS()

WRITE ( unit=output_unit, fmt='(a)' ) 'Pair distribution functions at a planar interface'

! Example default values
dz = 0.2 ! Spacing in z-direction
nz = 15 ! Number of z-points relative to interface location (-nz:+nz)
Expand Down
12 changes: 11 additions & 1 deletion hit_and_miss.f90
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,10 @@ PROGRAM hit_and_miss
! the software, you should not imply endorsement by the authors or publishers. !
!------------------------------------------------------------------------------------------------!

USE, INTRINSIC :: iso_fortran_env, ONLY : output_unit
! No parameters need be supplied by the user. The exact value of the integral is 5/3.
! For details, see Chapter 4 of the text.

USE, INTRINSIC :: iso_fortran_env, ONLY : output_unit, COMPILER_VERSION, COMPILER_OPTIONS

IMPLICIT NONE

Expand All @@ -35,6 +38,12 @@ PROGRAM hit_and_miss
REAL, PARAMETER :: v_0 = PRODUCT(r_0)
INTEGER :: tau, tau_shot, tau_hit

WRITE ( unit=output_unit, fmt='(a)' ) 'hit_and_miss'
WRITE ( unit=output_unit, fmt='(2a)' ) 'Compiler: ', COMPILER_VERSION()
WRITE ( unit=output_unit, fmt='(2a/)' ) 'Options: ', COMPILER_OPTIONS()

WRITE ( unit=output_unit, fmt='(a)' ) 'Estimates integral by crude hit-and-miss Monte Carlo'

CALL RANDOM_INIT ( .FALSE., .TRUE. ) ! Initialize random number generator
tau_hit = 0
tau_shot = 1000000
Expand All @@ -49,5 +58,6 @@ PROGRAM hit_and_miss
END DO
v = v_0 * REAL ( tau_hit ) / REAL ( tau_shot )
WRITE ( unit=output_unit, fmt='(a,f10.5)' ) 'Estimate = ', v
WRITE ( unit=output_unit, fmt='(a,f10.5)' ) 'Exact = ', 5.0/3.0

END PROGRAM hit_and_miss
Loading

0 comments on commit 1fcc4b5

Please sign in to comment.