\(\renewcommand{\AA}{\text{Å}}\)
1.3.1. The LIBLAMMPS Fortran Module
The LIBLAMMPS module provides an interface to call LAMMPS from
Fortran.  It is based on the LAMMPS C library interface and requires a
fully Fortran 2003-compatible compiler to be compiled.  It is designed
to be self-contained and not require any support functions written in C,
C++, or Fortran other than those in the C library interface and the
LAMMPS Fortran module itself.
While C libraries have a defined binary interface (ABI) and can thus be
used from multiple compiler versions from different vendors as long as
they are compatible with the hosting operating system, the same is not
true for Fortran programs.  Thus, the LAMMPS Fortran module needs to be
compiled alongside the code using it from the source code in
fortran/lammps.f90 and with the same compiler used to build the
rest of the Fortran code that interfaces to LAMMPS.  When linking, you
also need to link to the LAMMPS library.  A typical
command line for a simple program using the Fortran interface would be:
mpifort -o testlib.x lammps.f90 testlib.f90 -L. -llammps
Please note that the MPI compiler wrapper is only required when the calling the library from an MPI-parallelized program. Otherwise, using the plain Fortran compiler (gfortran, ifort, flang, etc.) will suffice, since there are no direct references to MPI library features, definitions and subroutine calls; MPI communicators are referred to by their integer index representation as required by the Fortran MPI interface. It may be necessary to link to additional libraries, depending on how LAMMPS was configured and whether the LAMMPS library was compiled as a static or dynamic library.
If the LAMMPS library itself has been compiled with MPI support, the
resulting executable will be able to run LAMMPS in parallel with
mpirun, mpiexec, or equivalent.  This may be either on the
“world” communicator or a sub-communicator created by the calling
Fortran code.  If, on the other hand, the LAMMPS library has been
compiled without MPI support, each LAMMPS instance will run
independently using just one processor.
Please also note that the order of the source files matters: the
lammps.f90 file needs to be compiled first, since it provides the
LIBLAMMPS module that would need to be imported by the calling
Fortran code in order to uses the Fortran interface.
A working example can be found together with equivalent examples in C and
C++ in the examples/COUPLE/simple folder of the LAMMPS distribution.
Fortran compiler compatibility
A fully Fortran 2003 compatible Fortran compiler is required. This means that currently only GNU Fortran 9 and later are compatible and thus the default compilers of Red Hat or CentOS 7 and Ubuntu 18.04 LTS and not compatible. Either newer compilers need to be installed or the Linux updated.
1.3.2. Creating or deleting a LAMMPS object
With the Fortran interface, the creation of a LAMMPS instance is included in the constructor for
creating the lammps() derived type.  To import the definition of
that type and its type-bound procedures, you need to add a USE LIBLAMMPS
statement.  Internally, it will call either
lammps_open_fortran() or lammps_open_no_mpi() from
the C library API to create the class instance.  All arguments are
optional and lammps_mpi_init() will be called automatically
if it is needed.  Similarly, a possible call to
lammps_mpi_finalize() is integrated into the close()
function and triggered with the optional logical argument set to
.TRUE.. Here is a simple example:
PROGRAM testlib
  USE LIBLAMMPS                 ! include the LAMMPS library interface
  IMPLICIT NONE
  TYPE(lammps) :: lmp           ! derived type to hold LAMMPS instance
  CHARACTER(LEN=12), PARAMETER :: args(3) = &
      [ CHARACTER(LEN=12) :: 'liblammps', '-log', 'none' ]
  ! create a LAMMPS instance (and initialize MPI)
  lmp = lammps(args)
  ! get and print numerical version code
  PRINT*, 'LAMMPS Version: ', lmp%version()
  ! delete LAMMPS instance (and shutdown MPI)
  CALL lmp%close(.TRUE.)
END PROGRAM testlib
It is also possible to pass command line flags from Fortran to C/C++ and thus make the resulting executable behave similarly to the standalone executable (it will ignore the -in/-i flag, though). This allows using the command line to configure accelerator and suffix settings, configure screen and logfile output, or to set index style variables from the command line and more. Here is a correspondingly adapted version of the previous example:
PROGRAM testlib2
  USE LIBLAMMPS                 ! include the LAMMPS library interface
  IMPLICIT NONE
  TYPE(lammps) :: lmp           ! derived type to hold LAMMPS instance
  CHARACTER(LEN=128), ALLOCATABLE :: command_args(:)
  INTEGER :: i, argc
  ! copy command line flags to `command_args()`
  argc = COMMAND_ARGUMENT_COUNT()
  ALLOCATE(command_args(0:argc))
  DO i=0, argc
    CALL GET_COMMAND_ARGUMENT(i, command_args(i))
  END DO
  ! create a LAMMPS instance (and initialize MPI)
  lmp = lammps(command_args)
  ! get and print numerical version code
  PRINT*, 'Program name:   ', command_args(0)
  PRINT*, 'LAMMPS Version: ', lmp%version()
  ! delete LAMMPS instance (and shuts down MPI)
  CALL lmp%close(.TRUE.)
  DEALLOCATE(command_args)
END PROGRAM testlib2
1.3.3. Executing LAMMPS commands
Once a LAMMPS instance is created, it is possible to “drive” the LAMMPS
simulation by telling LAMMPS to read commands from a file or to pass
individual or multiple commands from strings or lists of strings.  This
is done similarly to how it is implemented in the C library
interface. Before handing off the calls to the
C library interface, the corresponding Fortran versions of the calls
(file(), command(), commands_list(), and
commands_string()) have to make copies of the strings passed as
arguments so that they can be modified to be compatible with the
requirements of strings in C without affecting the original strings.
Those copies are automatically deleted after the functions return.
Below is a small demonstration of the uses of the different functions.
PROGRAM testcmd
  USE LIBLAMMPS
  TYPE(lammps) :: lmp
  CHARACTER(LEN=512) :: cmds
  CHARACTER(LEN=40), ALLOCATABLE :: cmdlist(:)
  CHARACTER(LEN=10) :: trimmed
  INTEGER :: i
  lmp = lammps()
  CALL lmp%file('in.melt')
  CALL lmp%command('variable zpos index 1.0')
  ! define 10 groups of 10 atoms each
  ALLOCATE(cmdlist(10))
  DO i=1, 10
    WRITE(trimmed,'(I10)') 10*i
    WRITE(cmdlist(i),'(A,I1,A,I10,A,A)')       &
        'group g', i-1, ' id ', 10*(i-1)+1, ':', ADJUSTL(trimmed)
  END DO
  CALL lmp%commands_list(cmdlist)
  ! run multiple commands from multi-line string
  cmds = 'clear' // NEW_LINE('A') //                       &
      'region  box block 0 2 0 2 0 2' // NEW_LINE('A') //  &
      'create_box 1 box' // NEW_LINE('A') //               &
      'create_atoms 1 single 1.0 1.0 ${zpos}'
  CALL lmp%commands_string(cmds)
  CALL lmp%close(.TRUE.)
END PROGRAM testcmd
1.3.4. Accessing system properties
The C library interface allows the extraction of different kinds of information about the active simulation instance and also—in some cases—to apply modifications to it, and the Fortran interface provides access to the same data using Fortran-style, C-interoperable data types. In some cases, the Fortran library interface makes pointers to internal LAMMPS data structures accessible; when accessing them through the library interfaces, special care is needed to avoid data corruption and crashes. Please see the documentation of the individual type-bound procedures for details.
Below is an example demonstrating some of the possible uses.
PROGRAM testprop
  USE LIBLAMMPS
  USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_double, c_int64_t, c_int
  USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY : OUTPUT_UNIT
  TYPE(lammps) :: lmp
  INTEGER(KIND=c_int64_t), POINTER :: natoms, ntimestep, bval
  REAL(KIND=c_double), POINTER :: dt, dval
  INTEGER(KIND=c_int), POINTER :: nfield, typ, ival
  INTEGER(KIND=c_int) :: i
  CHARACTER(LEN=11) :: key
  REAL(KIND=c_double) :: pe, ke
  lmp = lammps()
  CALL lmp%file('in.sysinit')
  natoms = lmp%extract_global('natoms')
  WRITE(OUTPUT_UNIT,'(A,I0,A)') 'Running a simulation with ', natoms, ' atoms'
  WRITE(OUTPUT_UNIT,'(I0,A,I0,A,I0,A)') lmp%extract_setting('nlocal'), &
      ' local and ', lmp%extract_setting('nghost'), ' ghost atoms. ', &
      lmp%extract_setting('ntypes'), ' atom types'
  CALL lmp%command('run 2 post no')
  ntimestep = lmp%last_thermo('step', 0)
  nfield = lmp%last_thermo('num', 0)
  WRITE(OUTPUT_UNIT,'(A,I0,A,I0)') 'Last thermo output on step: ', ntimestep, &
      ',  number of fields: ', nfield
  DO i=1, nfield
      key = lmp%last_thermo('keyword',i)
      typ = lmp%last_thermo('type',i)
      IF (typ == lmp%dtype%i32) THEN
          ival = lmp%last_thermo('data',i)
          WRITE(OUTPUT_UNIT,*) key, ':', ival
      ELSE IF (typ == lmp%dtype%i64) THEN
          bval = lmp%last_thermo('data',i)
          WRITE(OUTPUT_UNIT,*) key, ':', bval
      ELSE IF (typ == lmp%dtype%r64) THEN
          dval = lmp%last_thermo('data',i)
          WRITE(OUTPUT_UNIT,*) key, ':', dval
      END IF
  END DO
  dt = lmp%extract_global('dt')
  ntimestep = lmp%extract_global('ntimestep')
  WRITE(OUTPUT_UNIT,'(A,I0,A,F4.1,A)') 'At step: ', ntimestep, &
      '  Changing timestep from', dt, ' to 0.5'
  dt = 0.5_c_double
  CALL lmp%command('run 2 post no')
  WRITE(OUTPUT_UNIT,'(A,I0)') 'At step: ', ntimestep
  pe = lmp%get_thermo('pe')
  ke = lmp%get_thermo('ke')
  WRITE(OUTPUT_UNIT,*) 'PE = ', pe
  WRITE(OUTPUT_UNIT,*) 'KE = ', ke
  CALL lmp%close(.TRUE.)
END PROGRAM testprop
1.3.5. The LIBLAMMPS module API
Below are the detailed descriptions of definitions and interfaces
of the contents of the LIBLAMMPS Fortran interface to LAMMPS.
- type lammps
- Derived type that is the general class of the Fortran interface. It holds a reference to the - LAMMPSclass instance to which any of the included calls are forwarded.- Type fields:
- % handle [c_ptr] :: reference to the LAMMPS class 
- % style [type(lammps_style)] :: derived type to access lammps style constants 
- % type [type(lammps_type)] :: derived type to access lammps type constants 
- % dtype [type(lammps_dtype)] :: derived type to access lammps data type constants 
- % close [subroutine] :: - close()
- % error [subroutine] :: - error()
- % file [subroutine] :: - file()
- % command [subroutine] :: - command()
- % commands_list [subroutine] :: - commands_list()
- % commands_string [subroutine] :: - commands_string()
- % get_natoms [function] :: - get_natoms()
- % get_thermo [function] :: - get_thermo()
- % last_thermo [function] :: - last_thermo()
- % extract_box [subroutine] :: - extract_box()
- % reset_box [subroutine] :: - reset_box()
- % memory_usage [subroutine] :: - memory_usage()
- % get_mpi_comm [function] :: - get_mpi_comm()
- % extract_setting [function] :: - extract_setting()
- % extract_global [function] :: - extract_global()
- % extract_atom [function] :: - extract_atom()
- % extract_compute [function] :: - extract_compute()
- % extract_fix [function] :: - extract_fix()
- % extract_variable [function] :: - extract_variable()
- % set_variable [subroutine] :: - set_variable()
- % set_string_variable [subroutine] :: - set_set_string_variable()
- % set_internal_variable [subroutine] :: - set_internal_variable()
- % gather_atoms [subroutine] :: - gather_atoms()
- % gather_atoms_concat [subroutine] :: - gather_atoms_concat()
- % gather_atoms_subset [subroutine] :: - gather_atoms_subset()
- % scatter_atoms [subroutine] :: - scatter_atoms()
- % scatter_atoms_subset [subroutine] :: - scatter_atoms_subset()
- % gather_bonds [subroutine] :: - gather_bonds()
- % gather_angles [subroutine] :: - gather_angles()
- % gather_dihedrals [subroutine] :: - gather_dihedrals()
- % gather_impropers [subroutine] :: - gather_impropers()
- % gather [subroutine] :: - gather()
- % gather_concat [subroutine] :: - gather_concat()
- % gather_subset [subroutine] :: - gather_subset()
- % scatter [subroutine] :: - scatter()
- % scatter_subset [subroutine] :: - scatter_subset()
- % create_atoms [subroutine] :: - create_atoms()
- % find_pair_neighlist [function] :: - find_pair_neighlist()
- % find_fix_neighlist [function] :: - find_fix_neighlist()
- % find_compute_neighlist [function] :: - find_compute_neighlist()
- % neighlist_num_elements [function] :: - neighlist_num_elements()
- % neighlist_element_neighbors [subroutine] :: - neighlist_element_neighbors()
- % version [function] :: - version()
- % get_os_info [subroutine] :: - get_os_info()
- % config_has_mpi_support [function] :: - config_has_mpi_support()
- % config_has_gzip_support [function] :: - config_has_gzip_support()
- % config_has_png_support [function] :: - config_has_png_support()
- % config_has_jpeg_support [function] :: - config_has_jpeg_support()
- % config_has_ffmpeg_support [function] :: - config_has_ffmpeg_support()
- % config_has_exceptions [function] :: - config_has_exceptions()
- % config_has_package [function] :: - config_has_package()
- % config_package_count [function] :: - config_package_count()
- % config_package_name [function] :: - config_package_name()
- % installed_packages [subroutine] :: - installed_packages()
- % config_accelerator [function] :: - config_accelerator()
- % has_gpu_device [function] :: - has_gpu_device()
- % get_gpu_device_info [subroutine] :: - get_gpu_device_info()
- % has_style [function] :: - has_style()
- % style_count [function] :: - style_count()
- % style_name [function] :: - style_name()
- % has_id [function] :: - has_id()
- % id_count [function] :: - id_count()
- % id_name [subroutine] :: - id_name()
- % plugin_count [subroutine] :: - plugin_count()
- % plugin_name :: - plugin_name()
- % encode_image_flags [function] :: - encode_image_flags()
- % decode_image_flags [subroutine] :: - decode_image_flags()
- % set_fix_external_callback [subroutine] :: - set_fix_external_callback()
- % fix_external_get_force [function] :: - fix_external_get_force()
- % fix_external_set_energy_global [subroutine] :: - fix_external_set_energy_global()
- % fix_external_set_virial_global [subroutine] :: - fix_external_set_virial_global()
- % fix_external_set_energy_peratom [subroutine] :: - fix_external_set_energy_peratom()
- % fix_external_set_virial_peratom [subroutine] :: - fix_external_set_virial_peratom()
- % fix_external_set_vector_length [subroutine] :: - fix_external_set_vector_length()
- % fix_external_set_vector [subroutine] :: - fix_external_set_vector()
- % flush_buffers [subroutine] :: - flush_buffers()
- % is_running [function] :: - is_running()
- % force_timeout [subroutine] :: - force_timeout()
- % has_error [function] :: - has_error()
- % get_last_error_message [subroutine] :: - get_last_error_message()
 
 
- function lammps([args][,comm])
- This is the constructor for the Fortran class and will forward the arguments to a call to either - lammps_open_fortran()or- lammps_open_no_mpi(). If the LAMMPS library has been compiled with MPI support, it will also initialize MPI, if it has not already been initialized before.- The args argument with the list of command line parameters is optional and so it the comm argument with the MPI communicator. If comm is not provided, - MPI_COMM_WORLDis assumed. For more details please see the documentation of- lammps_open().- Options:
- args [character(len=*),dimension(:),optional] :: arguments as list of strings 
- comm [integer,optional] :: MPI communicator 
 
- Call to:
- Return:
- lammps :: an instance of the - lammpsderived type
 - Note - The - MPI_F08module, which defines Fortran 2008 bindings for MPI, is not directly supported by this interface due to the complexities of supporting both the- MPI_F08and- MPImodules at the same time. However, you should be able to use the- MPI_VALmember of the- MPI_commderived type to access the integer value of the communicator, such as in- PROGRAM testmpi USE LIBLAMMPS USE MPI_F08 TYPE(lammps) :: lmp lmp = lammps(comm=MPI_COMM_SELF%MPI_VAL) END PROGRAM testmpi 
- type lammps_style
- This derived type is there to provide a convenient interface for the style constants used with - extract_compute(),- extract_fix(), and- extract_variable(). Assuming your LAMMPS instance is called- lmp, these constants will be- lmp%style%global,- lmp%style%atom, and- lmp%style%local. These values are identical to the values described in- _LMP_STYLE_CONSTfor the C library interface.- Type fields:
- % global [integer(c_int)] :: used to request global data 
- % atom [integer(c_int)] :: used to request per-atom data 
- % local [integer(c_int)] :: used to request local data 
 
 
- type lammps_type
- This derived type is there to provide a convenient interface for the type constants used with - extract_compute(),- extract_fix(), and- extract_variable(). Assuming your LAMMPS instance is called- lmp, these constants will be- lmp%type%scalar,- lmp%type%vector, and- lmp%type%array. These values are identical to the values described in- _LMP_TYPE_CONSTfor the C library interface.- Type fields:
- % scalar [integer(c_int)] :: used to request scalars 
- % vector [integer(c_int)] :: used to request vectors 
- % array [integer(c_int)] :: used to request arrays (matrices) 
 
 
Procedures Bound to the lammps Derived Type
- subroutine close([finalize])
- This method will close down the LAMMPS instance through calling - lammps_close(). If the finalize argument is present and has a value of- .TRUE., then this subroutine also calls- lammps_kokkos_finalize()and- lammps_mpi_finalize().- Options:
- finalize [logical,optional] :: shut down the MPI environment of the LAMMPS library if - .TRUE..
- Call to:
- lammps_close()- lammps_mpi_finalize()- lammps_kokkos_finalize()
 
- subroutine error(error_type, error_text)
- This method is a wrapper around the - lammps_error()function and will dispatch an error through the LAMMPS Error class.- New in version 3Nov2022. - Parameters:
- error_type [integer(c_int)] :: constant to select which Error class function to call 
- error_text [character(len=*)] :: error message 
 
- Call to:
 
- subroutine file(filename)
- This method will call - lammps_file()to have LAMMPS read and process commands from a file.- Parameters:
- filename [character(len=*)] :: name of file with LAMMPS commands 
- Call to:
 
- subroutine command(cmd)
- This method will call - lammps_command()to have LAMMPS execute a single command.- Parameters:
- cmd [character(len=*)] :: single LAMMPS command 
- Call to:
 
- subroutine commands_list(cmds)
- This method will call - lammps_commands_list()to have LAMMPS execute a list of input lines.- Parameters:
- cmd [character(len=*),dimension(:)] :: list of LAMMPS input lines 
- Call to:
 
- subroutine commands_string(str)
- This method will call - lammps_commands_string()to have LAMMPS execute a block of commands from a string.- Parameters:
- str [character(len=*)] :: LAMMPS input in string 
- Call to:
 
- function get_natoms()
- This function will call - lammps_get_natoms()and return the number of atoms in the system.- Call to:
- Return:
- natoms [real(c_double)] :: number of atoms 
 - Note - If you would prefer to get the number of atoms in its native format (i.e., as a 32- or 64-bit integer, depending on how LAMMPS was compiled), this can be extracted with - extract_global().
- function get_thermo(name)
- This function will call - lammps_get_thermo()and return the value of the corresponding thermodynamic keyword.- New in version 3Nov2022. - Parameters:
- name [character(len=*)] :: string with the name of the thermo keyword 
- Call to:
- Return:
- value [real(c_double)] :: value of the requested thermo property or 0.0_c_double 
 
- function last_thermo(what, index)
- This function will call - lammps_last_thermo()and returns either a string or a pointer to a cached copy of LAMMPS last thermodynamic output, depending on the data requested through what. Note that index uses 1-based indexing to access thermo output columns.- New in version 15Jun2023. - Note that this function actually does not return a value, but rather associates the pointer on the left side of the assignment to point to internal LAMMPS data (with the exception of string data, which are copied and returned as ordinary Fortran strings). Pointers must be of the correct data type to point to said data (typically - INTEGER(c_int),- INTEGER(c_int64_t), or- REAL(c_double)). The pointer being associated with LAMMPS data is type-checked at run-time via an overloaded assignment operator. The pointers returned by this function point to temporary, read-only data that may be overwritten at any time, so their target values need to be copied to local storage if they are supposed to persist.- For example, - PROGRAM thermo USE LIBLAMMPS USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_double, c_int64_t, c_int TYPE(lammps) :: lmp INTEGER(KIND=c_int64_t), POINTER :: ntimestep, bval REAL(KIND=c_double), POINTER :: dval INTEGER(KIND=c_int), POINTER :: nfield, typ, ival INTEGER(KIND=c_int) :: i CHARACTER(LEN=11) :: key lmp = lammps() CALL lmp%file('in.sysinit') ntimestep = lmp%last_thermo('step', 0) nfield = lmp%last_thermo('num', 0) PRINT*, 'Last thermo output on step: ', ntimestep, ' Number of fields: ', nfield DO i=1, nfield key = lmp%last_thermo('keyword',i) typ = lmp%last_thermo('type',i) IF (typ == lmp%dtype%i32) THEN ival = lmp%last_thermo('data',i) PRINT*, key, ':', ival ELSE IF (typ == lmp%dtype%i64) THEN bval = lmp%last_thermo('data',i) PRINT*, key, ':', bval ELSE IF (typ == lmp%dtype%r64) THEN dval = lmp%last_thermo('data',i) PRINT*, key, ':', dval END IF END DO CALL lmp%close(.TRUE.) END PROGRAM thermo - would extract the last timestep where thermo output was done and the number of columns it printed. Then it loops over the columns to print out column header keywords and the corresponding data. - Note - If - last_thermo()returns a string, the string must have a length greater than or equal to the length of the string (not including the terminal- NULLcharacter) that LAMMPS returns. If the variable’s length is too short, the string will be truncated. As usual in Fortran, strings are padded with spaces at the end. If you use an allocatable string, the string must be allocated prior to calling this function.- Parameters:
- what [character(len=*)] :: string with the name of the thermo keyword 
- index [integer(c_int)] :: 1-based column index 
 
- Call to:
- Return:
- pointer [polymorphic] :: pointer to LAMMPS data. The left-hand side of the assignment should be either a string (if expecting string data) or a C-compatible pointer (e.g., - INTEGER(c_int), POINTER :: nlocal) to the extracted property.
 - Warning - Modifying the data in the location pointed to by the returned pointer may lead to inconsistent internal data and thus may cause failures, crashes, or bogus simulations. In general, it is much better to use a LAMMPS input command that sets or changes these parameters. Using an input command will take care of all side effects and necessary updates of settings derived from such settings. 
- subroutine extract_box([boxlo][, boxhi][, xy][, yz][, xz][, pflags][, boxflag])
- This subroutine will call - lammps_extract_box(). All parameters are optional, though obviously at least one should be present. The parameters pflags and boxflag are stored in LAMMPS as integers, but should be declared as- LOGICALvariables when calling from Fortran.- New in version 3Nov2022. - Options:
- boxlo [real(c_double),dimension(3),optional] :: vector in which to store lower-bounds of simulation box 
- boxhi [real(c_double),dimension(3),optional] :: vector in which to store upper-bounds of simulation box 
- xy [real(c_double),optional] :: variable in which to store xy tilt factor 
- yz [real(c_double),optional] :: variable in which to store yz tilt factor 
- xz [real(c_double),optional] :: variable in which to store xz tilt factor 
- pflags [logical,dimension(3),optional] :: vector in which to store periodicity flags ( - .TRUE.means periodic in that dimension)
- boxflag [logical,optional] :: variable in which to store boolean denoting whether the box will change during a simulation ( - .TRUE.means box will change)
 
- Call to:
 
Note
Note that a frequent use case of this function is to extract only one or more of the options rather than all seven. For example, assuming “lmp” represents a properly-initialized LAMMPS instance, the following code will extract the periodic box settings into the variable “periodic”:
! code to start up
LOGICAL :: periodic(3)
! code to initialize LAMMPS / run things / etc.
CALL lmp%extract_box(pflags = periodic)
- subroutine reset_box(boxlo, boxhi, xy, yz, xz)
- This subroutine will call - lammps_reset_box(). All parameters are required.- New in version 3Nov2022. - Parameters:
- boxlo [real(c_double),dimension(3)] :: vector of three doubles containing the lower box boundary 
- boxhi [real(c_double),dimension(3)] :: vector of three doubles containing the upper box boundary 
- xy [real(c_double)] :: x–y tilt factor 
- yz [real(c_double)] :: y–z tilt factor 
- xz [real(c_double)] :: x–z tilt factor 
 
- Call to:
 
- subroutine memory_usage(meminfo)
- This subroutine will call - lammps_memory_usage()and store the result in the three-element array meminfo.- New in version 3Nov2022. - Parameters:
- meminfo [real(c_double),dimension(3)] :: vector of three doubles in which to store memory usage data 
- Call to:
 
- function get_mpi_comm()
- This function returns a Fortran representation of the LAMMPS “world” communicator. - New in version 3Nov2022. - Call to:
- Return:
- comm [integer] :: Fortran integer equivalent to the MPI communicator LAMMPS is using 
 - Note - The C library interface currently returns type - intinstead of type- MPI_Fint, which is the C type corresponding to Fortran- INTEGERtypes of the default kind. On most compilers, these are the same anyway, but this interface exchanges values this way to avoid warning messages.- Note - The - MPI_F08module, which defines Fortran 2008 bindings for MPI, is not directly supported by this function. However, you should be able to convert between the two using the MPI_VAL member of the communicator. For example,- USE MPI_F08 USE LIBLAMMPS TYPE(lammps) :: lmp TYPE(MPI_Comm) :: comm ! ... [commands to set up LAMMPS/etc.] comm%MPI_VAL = lmp%get_mpi_comm() - should assign an - MPI_F08communicator properly.
- function extract_setting(keyword)
- Query LAMMPS about global settings. See the documentation for the - lammps_extract_setting()function from the C library.- New in version 3Nov2022. - Parameters:
- keyword [character(len=*)] :: string containing the name of the thermo keyword 
- Call to:
- Return:
- setting [integer(c_int)] :: value of the queried setting or \(-1\) if unknown 
 
- function extract_global(name)
- This function calls - lammps_extract_global()and returns either a string or a pointer to internal global LAMMPS data, depending on the data requested through name.- New in version 3Nov2022. - Note that this function actually does not return a value, but rather associates the pointer on the left side of the assignment to point to internal LAMMPS data (with the exception of string data, which are copied and returned as ordinary Fortran strings). Pointers must be of the correct data type to point to said data (typically - INTEGER(c_int),- INTEGER(c_int64_t), or- REAL(c_double)) and have compatible kind and rank. The pointer being associated with LAMMPS data is type-, kind-, and rank-checked at run-time via an overloaded assignment operator. The pointers returned by this function are generally persistent; therefore it is not necessary to call the function again unless a clear command command has been issued, which wipes out and recreates the contents of the- LAMMPSclass.- For example, - PROGRAM demo USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int64_t, c_int, c_double USE LIBLAMMPS TYPE(lammps) :: lmp INTEGER(c_int), POINTER :: nlocal => NULL() INTEGER(c_int64_t), POINTER :: ntimestep => NULL() REAL(c_double), POINTER :: dt => NULL() CHARACTER(LEN=10) :: units lmp = lammps() ! other commands nlocal = lmp%extract_global('nlocal') ntimestep = lmp%extract_global('ntimestep') dt = lmp%extract_global('dt') units = lmp%extract_global('units') ! more commands lmp.close(.TRUE.) END PROGRAM demo - would extract the number of atoms on this processor, the current time step, the size of the current time step, and the units being used into the variables nlocal, ntimestep, dt, and units, respectively. - Note - If - extract_global()returns a string, the string must have a length greater than or equal to the length of the string (not including the terminal- NULLcharacter) that LAMMPS returns. If the variable’s length is too short, the string will be truncated. As usual in Fortran, strings are padded with spaces at the end. If you use an allocatable string, the string must be allocated prior to calling this function, but you can automatically reallocate it to the correct length after the function returns, viz.,- PROGRAM test USE LIBLAMMPS TYPE(lammps) :: lmp CHARACTER(LEN=:), ALLOCATABLE :: str lmp = lammps() CALL lmp%command('units metal') ALLOCATE(CHARACTER(LEN=80) :: str) str = lmp%extract_global('units') str = TRIM(str) ! re-allocates to length len_trim(str) here PRINT*, LEN(str), LEN_TRIM(str) END PROGRAM test - will print the number 5 (the length of the word “metal”) twice. - Parameters:
- name [character(len=*)] :: string with the name of the property to extract 
- Call to:
- Return:
- pointer [polymorphic] :: pointer to LAMMPS data. The left-hand side of the assignment should be either a string (if expecting string data) or a C-compatible pointer (e.g., - INTEGER(c_int), POINTER :: nlocal) to the extracted property. If expecting vector data, the pointer should have dimension “:”.
 - Warning - Modifying the data in the location pointed to by the returned pointer may lead to inconsistent internal data and thus may cause failures, crashes, or bogus simulations. In general, it is much better to use a LAMMPS input command that sets or changes these parameters. Using an input command will take care of all side effects and necessary updates of settings derived from such settings. 
- function extract_atom(name)
- This function calls - lammps_extract_atom()and returns a pointer to LAMMPS data tied to the- Atomclass, depending on the data requested through name.- New in version 3Nov2022. - Note that this function actually does not return a pointer, but rather associates the pointer on the left side of the assignment to point to internal LAMMPS data. Pointers must be of the correct type, kind, and rank (e.g., - INTEGER(c_int), DIMENSION(:)for “type”, “mask”, or “id”;- INTEGER(c_int64_t), DIMENSION(:)for “id” if LAMMPS was compiled with the- -DLAMMPS_BIGBIGflag;- REAL(c_double), DIMENSION(:,:)for “x”, “v”, or “f”; and so forth). The pointer being associated with LAMMPS data is type-, kind-, and rank-checked at run-time.- Parameters:
- name [character(len=*)] :: string with the name of the property to extract 
- Call to:
- Return:
- pointer [polymorphic] :: pointer to LAMMPS data. The left-hand side of the assignment should be a C-interoperable pointer of appropriate kind and rank (e.g., - INTEGER(c_int), POINTER :: mask(:)) to the extracted property. If expecting vector data, the pointer should have dimension “:”; if expecting matrix data, the pointer should have dimension “:,:”.
 - Warning - Pointers returned by this function are generally not persistent, as per-atom data may be redistributed, reallocated, and reordered at every re-neighboring operation. It is advisable to re-bind pointers using - extract_atom()between runs.- Array index order - Two-dimensional arrays returned from - extract_atom()will be transposed from equivalent arrays in C, and they will be indexed from 1 instead of 0. For example, in C,- void *lmp; double **x; /* more code to setup, etc. */ x = lammps_extract_atom(lmp, "x"); printf("%f\n", x[5][1]); - will print the y-coordinate of the sixth atom on this processor. Conversely, - TYPE(lammps) :: lmp REAL(c_double), DIMENSION(:,:), POINTER :: x => NULL() ! more code to setup, etc. x = lmp%extract_atom("x") PRINT '(f0.6)', x(2,6) - will print the y-coordinate of the sixth atom on this processor (note the transposition of the two indices). This is not a choice, but rather a consequence of the different conventions adopted by the Fortran and C standards decades ago: in C, the block of data - 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 - interpreted as a \(4\times4\) matrix would be \[\begin{split}\begin{bmatrix} 1 & 2 & 3 & 4 \\ 5 & 6 & 7 & 8 \\ 9 & 10 & 11 & 12 \\ 13 & 14 & 15 & 16 \end{bmatrix},\end{split}\]- that is, in row-major order. In Fortran, the same block of data is interpreted in column-major order, namely, \[\begin{split}\begin{bmatrix} 1 & 5 & 9 & 13 \\ 2 & 6 & 10 & 14 \\ 3 & 7 & 11 & 15 \\ 4 & 8 & 12 & 16 \end{bmatrix}.\end{split}\]- This difference in interpretation of the same block of data by the two languages means, in effect, that matrices from C or C++ will be transposed when interpreted in Fortran. - Note - If you would like the indices to start at 0 instead of 1 (which follows typical notation in C and C++, but not Fortran), you can create another pointer and associate it thus: - REAL(c_double), DIMENSION(:,:), POINTER :: x, x0 x = lmp%extract_atom("x") x0(0:,0:) => x - The above would cause the dimensions of x to be (1:3, 1:nmax) and those of x0 to be (0:2, 0:nmax\(-\)1). 
- function extract_compute(id, style, type)
- This function calls - lammps_extract_compute()and returns a pointer to LAMMPS data tied to the- Computeclass, specifically data provided by the compute identified by id. Computes may provide global, per-atom, or local data, and those data may be a scalar, a vector, or an array. Since computes may provide multiple kinds of data, the user is required to specify which set of data is to be returned through the style and type variables.- New in version 3Nov2022. - Note that this function actually does not return a value, but rather associates the pointer on the left side of the assignment to point to internal LAMMPS data. Pointers must be of the correct data type to point to said data (i.e., - REAL(c_double)) and have compatible rank. The pointer being associated with LAMMPS data is type-, kind-, and rank-checked at run-time via an overloaded assignment operator.- For example, - TYPE(lammps) :: lmp REAL(c_double), DIMENSION(:), POINTER :: COM ! code to setup, create atoms, etc. CALL lmp%command('compute COM all com') COM = lmp%extract_compute('COM', lmp%style%global, lmp%style%type) - will bind the variable COM to the center of mass of the atoms created in your simulation. The vector in this case has length 3; the length (or, in the case of array data, the number of rows and columns) is determined for you based on data from the - Computeclass.- Array index order - Two-dimensional arrays returned from - extract_compute()will be transposed from equivalent arrays in C, and they will be indexed from 1 instead of 0. See the note at- extract_atom()for further details.- The following combinations are possible (assuming - lmpis the name of your LAMMPS instance):- Style - Type - Type to assign to - Returned data - lmp%style%global- lmp%type%scalar- REAL(c_double), POINTER- Global scalar - lmp%style%global- lmp%type%vector- REAL(c_double), DIMENSION(:), POINTER- Global vector - lmp%style%global- lmp%type%array- REAL(c_double), DIMENSION(:,:), POINTER- Global array - lmp%style%atom- lmp%type%vector- REAL(c_double), DIMENSION(:), POINTER- Per-atom vector - lmp%style%atom- lmp%type%array- REAL(c_double), DIMENSION(:,:), POINTER- Per-atom array - lmp%style%local- lmp%type%vector- REAL(c_double), DIMENSION(:), POINTER- Local vector - lmp%style%local- lmp%type%array- REAL(c_double), DIMENSION(:,:), POINTER- Local array - Parameters:
- id [character(len=*)] :: compute ID from which to extract data 
- style [integer(c_int)] :: value indicating the style of data to extract (global, per-atom, or local) 
- type [integer(c_int)] :: value indicating the type of data to extract (scalar, vector, or array) 
 
- Call to:
- Return:
- pointer [polymorphic] :: pointer to LAMMPS data. The left-hand side of the assignment should be a C-compatible pointer (e.g., - REAL(c_double), POINTER :: x) to the extracted property. If expecting vector data, the pointer should have dimension “:”; if expecting array (matrix) data, the pointer should have dimension “:,:”.
 - Note - If the compute’s data are not already computed for the current step, the compute will be invoked. LAMMPS cannot easily check at that time if it is valid to invoke a compute, so it may fail with an error. The caller has to check to avoid such an error. - Warning - The pointers returned by this function are generally not persistent, since the computed data may be re-distributed, re-allocated, and re-ordered at every invocation. It is advisable to re-invoke this function before the data are accessed or make a copy if the data are to be used after other LAMMPS commands have been issued. Do not modify the data returned by this function. 
- function extract_fix(id, style, type[, nrow][, ncol])
- This function calls - lammps_extract_fix()and returns a pointer to LAMMPS data tied to the- Fixclass, specifically data provided by the fix identified by id. Fixes may provide global, per-atom, or local data, and those data may be a scalar, a vector, or an array. Since many fixes provide multiple kinds of data, the user is required to specify which set of data is to be returned through the style and type variables.- New in version 3Nov2022. - Global data are calculated at the time they are requested and are only available element-by-element. As such, the user is expected to provide the nrow variable to specify which element of a global vector or the nrow and ncol variables to specify which element of a global array the user wishes LAMMPS to return. The ncol variable is optional for global scalar or vector data, and both nrow and ncol are optional when a global scalar is requested, as well as when per-atom or local data are requested. The following combinations are possible (assuming - lmpis the name of your LAMMPS instance):- Style - Type - nrow - ncol - Type to assign to - Returned data - lmp%style%global- lmp%type%scalar- Ignored - Ignored - REAL(c_double)- Global scalar - lmp%style%global- lmp%type%vector- Required - Ignored - REAL(c_double)- Element of global vector - lmp%style%global- lmp%type%array- Required - Required - REAL(c_double)- Element of global array - lmp%style%atom- lmp%type%scalar- (not allowed) - lmp%style%atom- lmp%type%vector- Ignored - Ignored - REAL(c_double), DIMENSION(:), POINTER- Per-atom vector - lmp%style%atom- lmp%type%array- Ignored - Ignored - REAL(c_double), DIMENSION(:,:), POINTER- Per-atom array - lmp%style%local- lmp%type%scalar- (not allowed) - lmp%style%local- lmp%type%vector- Ignored - Ignored - REAL(c_double), DIMENSION(:), POINTER- Per-atom vector - lmp%style%local- lmp%type%array- Ignored - Ignored - REAL(c_double), DIMENSION(:,:), POINTER- Per-atom array - In the case of global data, this function returns a value of type - REAL(c_double). For per-atom or local data, this function does not return a value but instead associates the pointer on the left side of the assignment to point to internal LAMMPS data. Pointers must be of the correct type and kind to point to said data (i.e.,- REAL(c_double)) and have compatible rank. The pointer being associated with LAMMPS data is type-, kind-, and rank-checked at run-time via an overloaded assignment operator.- For example, - TYPE(lammps) :: lmp REAL(c_double) :: dr, dx, dy, dz ! more code to set up, etc. lmp%command('fix george all recenter 2 2 2') ! more code dr = lmp%extract_fix("george", lmp%style%global, lmp%style%scalar) dx = lmp%extract_fix("george", lmp%style%global, lmp%style%vector, 1) dy = lmp%extract_fix("george", lmp%style%global, lmp%style%vector, 2) dz = lmp%extract_fix("george", lmp%style%global, lmp%style%vector, 3) - will extract the global scalar calculated by fix recenter into the variable dr and the three elements of the global vector calculated by fix recenter into the variables dx, dy, and dz, respectively. - If asked for per-atom or local data, - extract_compute()returns a pointer to actual LAMMPS data. The pointer so returned will have the appropriate size to match the internal data, and will be type/kind/rank-checked at the time of the assignment. For example,- TYPE(lammps) :: lmp REAL(c_double), DIMENSION(:), POINTER :: r ! more code to set up, etc. lmp%command('fix state all store/state 0 x y z') ! more code r = lmp%extract_fix('state', lmp%style%atom, lmp%type%array) - will bind the pointer r to internal LAMMPS data representing the per-atom array computed by fix store/state when three inputs are specified. Similarly, - TYPE(lammps) :: lmp REAL(c_double), DIMENSION(:), POINTER :: x ! more code to set up, etc. lmp%command('fix state all store/state 0 x') ! more code x = lmp%extract_fix('state', lmp%style%atom, lmp%type%vector) - will associate the pointer x with internal LAMMPS data corresponding to the per-atom vector computed by fix store/state when only one input is specified. Similar examples with - lmp%style%atomreplaced by- lmp%style%localwill extract local data from fixes that define local vectors and/or arrays.- Warning - The pointers returned by this function for per-atom or local data are generally not persistent, since the computed data may be redistributed, reallocated, and reordered at every invocation of the fix. It is thus advisable to re-invoke this function before the data are accessed or to make a copy if the data are to be used after other LAMMPS commands have been issued. - Note - LAMMPS cannot easily check if it is valid to access the data, so it may fail with an error. The caller has to avoid such an error. - Parameters:
- id [character(len=*)] :: string with the name of the fix from which to extract data 
- style [integer(c_int)] :: value indicating the style of data to extract (global, per-atom, or local) 
- type [integer(c_int)] :: value indicating the type of data to extract (scalar, vector, or array) 
- nrow [integer(c_int)] :: row index (used only for global vectors and arrays) 
- ncol [integer(c_int)] :: column index (only used for global arrays) 
 
- Call to:
- Return:
- data [polymorphic] :: LAMMPS data (for global data) or a pointer to LAMMPS data (for per-atom or local data). The left-hand side of the assignment should be of type - REAL(c_double)and have appropriate rank (i.e.,- DIMENSION(:)if expecting per-atom or local vector data and- DIMENSION(:,:)if expecting per-atom or local array data). If expecting local or per-atom data, it should have the- POINTERattribute, but if expecting global data, it should be an ordinary (non-- POINTER) variable.
 - Array index order - Two-dimensional global, per-atom, or local array data from - extract_fix()will be transposed from equivalent arrays in C (or in the ordinary LAMMPS interface accessed through thermodynamic output), and they will be indexed from 1, not 0. This is true even for global data, which are returned as scalars—this is done primarily so the interface is consistent, as there is no choice but to transpose the indices for per-atom or local array data. See the similar note under- extract_atom()for further details.
- function extract_variable(name[, group])
- This function calls - lammps_extract_variable()and returns a scalar, vector, or string containing the value of the variable identified by name. When the variable is an equal-style variable (or one compatible with that style such as internal), the variable is evaluated and the corresponding value returned. When the variable is an atom-style variable, the variable is evaluated and a vector of values is returned. With all other variables, a string is returned. The group argument is only used for atom style variables and is ignored otherwise. If group is absent for atom-style variables, the group is assumed to be “all”.- New in version 3Nov2022. - This function returns the values of the variables, not pointers to them. Vectors pointing to atom-style variables should be of type - REAL(c_double), be of rank 1 (i.e.,- DIMENSION(:)), and have the- ALLOCATABLEattribute.- Note - Unlike the C library interface, the Fortran interface does not require you to deallocate memory when you are through; this is done for you, behind the scenes. - For example, - TYPE(lammps) :: lmp REAL(c_double) :: area ! more code to set up, etc. lmp%command('variable A equal lx*ly') ! more code area = lmp%extract_variable("A") - will extract the x–y cross-sectional area of the simulation into the variable area. - Parameters:
- name [character(len=*)] :: variable name to evaluate 
- Options:
- group [character(len=*),optional] :: group for which to extract per-atom data (if absent, use “all”) 
- Call to:
- Return:
- data [polymorphic] :: scalar of type - REAL(c_double)(for equal-style variables and others that are equal-compatible), vector of type- REAL(c_double), DIMENSION(:), ALLOCATABLEfor atom- or vector-style variables, or- CHARACTER(LEN=*)for string-style and compatible variables. Strings whose length is too short to hold the result will be truncated. Allocatable strings must be allocated before this function is called; see note at- extract_global()regarding allocatable strings. Allocatable arrays (for atom- and vector-style data) will be reallocated on assignment.
 
Note
LAMMPS cannot easily check if it is valid to access the data referenced by the variables (e.g., computes, fixes, or thermodynamic info), so it may fail with an error. The caller has to make certain that the data are extracted only when it is safe to evaluate the variable and thus an error and crash are avoided.
- subroutine set_variable(name, str)
- Set the value of a string-style variable. - Deprecated since version 7Feb2024. - This function assigns a new value from the string str to the string-style variable name. If name does not exist or is not a string-style variable, an error is generated. - Warning - This subroutine is deprecated and - set_string_variable()should be used instead.- Parameters:
- name [character(len=*)] :: name of the variable 
- str [character(len=*)] :: new value to assign to the variable 
 
- Call to:
 
- subroutine set_string_variable(name, str)
- Set the value of a string-style variable. - New in version 7Feb2024. - This function assigns a new value from the string str to the string-style variable name. If name does not exist or is not a string-style variable, an error is generated. - Parameters:
- name [character(len=*)] :: name of the variable 
- str [character(len=*)] :: new value to assign to the variable 
 
- Call to:
 
- subroutine set_internal_variable(name, val)
- Set the value of a internal-style variable. - New in version 7Feb2024. - This function assigns a new value from the floating-point number val to the internal-style variable name. If name does not exist or is not an internal-style variable, an error is generated. - Parameters:
- name [character(len=*)] :: name of the variable 
- val [read(c_double)] :: new value to assign to the variable 
 
- Call to:
 
- subroutine gather_atoms(name, count, data)
- This function calls - lammps_gather_atoms()to gather the named atom-based entity for all atoms on all processors and return it in the vector data. The vector data will be ordered by atom ID, which requires consecutive atom IDs (1 to natoms).- New in version 3Nov2022. - If you need a similar array but have non-consecutive atom IDs, see - gather_atoms_concat(); for a similar array but for a subset of atoms, see- gather_atoms_subset().- The data array will be ordered in groups of count values, sorted by atom ID (e.g., if name is x and count = 3, then data = [x(1,1), x(2,1), x(3,1), x(1,2), x(2,2), x(3,2), x(1,3), \(\dots\)]); data must be - ALLOCATABLEand will be allocated to length (count \(\times\) natoms), as queried by- get_natoms().- This function is not compatible with - -DLAMMPS_BIGBIG.- Parameters:
- name [character(len=*)] :: desired quantity (e.g., x or mask) 
- count [integer(c_int)] :: number of per-atom values you expect per atom (e.g., 1 for type, mask, or charge; 3 for x, v, or f). Use count = 3 with image if you want a single image flag unpacked into x/y/z components. 
- data [polymorphic,dimension(:),allocatable] :: array into which to store the data. Array must have the - ALLOCATABLEattribute and be of rank 1 (i.e.,- DIMENSION(:)). If this array is already allocated, it will be reallocated to fit the length of the incoming data. It should have type- INTEGER(c_int)if expecting integer data and- REAL(c_double)if expecting floating-point data.
 
- Call to:
 - Note - If you want data from this function to be accessible as a two-dimensional array, you can declare a rank-2 pointer and reassign it, like so: - USE, INTRINSIC :: ISO_C_BINDING USE LIBLAMMPS TYPE(lammps) :: lmp REAL(c_double), DIMENSION(:), ALLOCATABLE, TARGET :: xdata REAL(c_double), DIMENSION(:,:), POINTER :: x ! other code to set up, etc. CALL lmp%gather_atoms('x',3,xdata) x(1:3,1:size(xdata)/3) => xdata - You can then access the y-component of atom 3 with - x(2,3). See the note about array index order at- extract_atom().
- subroutine gather_atoms_concat(name, count, data)
- This function calls - lammps_gather_atoms_concat()to gather the named atom-based entity for all atoms on all processors and return it in the vector data.- New in version 3Nov2022. - The vector data will not be ordered by atom ID, and there is no restriction on the IDs being consecutive. If you need the IDs, you can do another - gather_atoms_concat()with name set to- id.- If you need a similar array but have consecutive atom IDs, see - gather_atoms(); for a similar array but for a subset of atoms, see- gather_atoms_subset().- This function is not compatible with - -DLAMMPS_BIGBIG.- Parameters:
- name [character(len=*)] :: desired quantity (e.g., x or mask) 
- count [integer(c_int)] :: number of per-atom values you expect per atom (e.g., 1 for type, mask, or charge; 3 for x, v, or f). Use count = 3 with image if you want a single image flag unpacked into x/y/z components. 
- data [polymorphic,dimension(:),allocatable] :: array into which to store the data. Array must have the - ALLOCATABLEattribute and be of rank 1 (i.e.,- DIMENSION(:)). If this array is already allocated, it will be reallocated to fit the length of the incoming data. It should have type- INTEGER(c_int)if expecting integer data and- REAL(c_double)if expecting floating-point data.
 
- Call to:
 
- subroutine gather_atoms_subset(name, count, ids, data)
- This function calls - lammps_gather_atoms_subset()to gather the named atom-based entity for the atoms in the array ids from all processors and return it in the vector data.- New in version 3Nov2022. - This subroutine gathers data for the requested atom IDs and stores them in a one-dimensional allocatable array. The data will be ordered by atom ID, but there is no requirement that the IDs be consecutive. If you wish to return a similar array for all the atoms, use - gather_atoms()or- gather_atoms_concat().- The data array will be in groups of count values, sorted by atom ID in the same order as the array ids (e.g., if name is x, count = 3, and ids is [100, 57, 210], then data might look like [x(1,100), x(2,100), x(3,100), x(1,57), x(2,57), x(3,57), x(1,210), \(\dots\)]; ids must be provided by the user, and data must be of rank 1 (i.e., - DIMENSION(:)) and have the- ALLOCATABLEattribute.- This function is not compatible with - -DLAMMPS_BIGBIG.- Parameters:
- name [character(len=*)] :: desired quantity (e.g., x or mask) 
- count [integer(c_int)] :: number of per-atom values you expect per atom (e.g., 1 for type, mask, or charge; 3 for x, v, or f). Use count = 3 with image if you want a single image flag unpacked into x/y/z components. 
- ids [integer(c_int),dimension(:)] :: atom IDs corresponding to the atoms to be gathered 
- data [polymorphic,dimension(:),allocatable] :: array into which to store the data. Array must have the - ALLOCATABLEattribute and be of rank 1 (i.e.,- DIMENSION(:)). If this array is already allocated, it will be reallocated to fit the length of the incoming data. It should have type- INTEGER(c_int)if expecting integer data and- REAL(c_double)if expecting floating-point data.
 
- Call to:
 
- subroutine scatter_atoms(name, data)
- This function calls - lammps_scatter_atoms()to scatter the named atom-based entities in data to all processors.- New in version 3Nov2022. - This subroutine takes data stored in a one-dimensional array supplied by the user and scatters them to all atoms on all processors. The data must be ordered by atom ID, with the requirement that the IDs be consecutive. Use - scatter_atoms_subset()to scatter data for some (or all) atoms, in any order.- The data array needs to be ordered in groups of count values, sorted by atom ID (e.g., if name is x and count = 3, then data = [x(1,1), x(2,1), x(3,1), x(1,2), x(2,2), x(3,2), x(1,3), \(\dots\)]); data must be of length natoms or 3*natoms. - Parameters:
- name [character(len=*)] :: quantity to be scattered (e.g., x or charge) 
- data [polymorphic,dimension(:)] :: per-atom values packed in a one-dimensional array containing the data to be scattered. This array must have length natoms (e.g., for type or charge) or length natoms\({}\times 3\) (e.g., for x or f). The array data must be rank 1 (i.e., - DIMENSION(:)) and be of type- INTEGER(c_int)(e.g., for mask or type) or of type- REAL(c_double)(e.g., for x or charge or f).
 
- Call to:
 
- subroutine scatter_atoms_subset(name, ids, data)
- This function calls - lammps_scatter_atoms_subset()to scatter the named atom-based entities in data to all processors.- New in version 3Nov2022. - This subroutine takes data stored in a one-dimensional array supplied by the user and scatters them to a subset of atoms on all processors. The array data contains data associated with atom IDs, but there is no requirement that the IDs be consecutive, as they are provided in a separate array, ids. Use - scatter_atoms()to scatter data for all atoms, in order.- The data array needs to be organized in groups of 1 or 3 values, depending on which quantity is being scattered, with the groups in the same order as the array ids. For example, if you want data to be the array [x(1,1), x(2,1), x(3,1), x(1,100), x(2,100), x(3,100), x(1,57), x(2,57), x(3,57)], then ids would be [1, 100, 57] and name would be x. - Parameters:
- name [character(len=*)] :: quantity to be scattered (e.g., x or charge) 
- ids [integer(c_int),dimension(:)] :: atom IDs corresponding to the atoms being scattered 
- data [polymorphic,dimension(:)] :: per-atom values packed into a one-dimensional array containing the data to be scattered. This array must have either the same length as ids (for mask, type, etc.) or three times its length (for x, f, etc.); the array must be rank 1 and be of type - INTEGER(c_int)(e.g., for mask or type) or of type- REAL(c_double)(e.g., for charge, x, or f).
 
- Call to:
 
- subroutine gather_bonds(data)
- Gather type and constituent atom information for all bonds. - New in version 3Nov2022. - This function copies the list of all bonds into an allocatable array. The array will be filled with (bond type, bond atom 1, bond atom 2) for each bond. The array is allocated to the right length (i.e., three times the number of bonds). The array data must be of the same type as the LAMMPS - taginttype, which is equivalent to either- INTEGER(c_int)or- INTEGER(c_int64_t), depending on whether- -DLAMMPS_BIGBIGwas used when LAMMPS was built. If the supplied array does not match, an error will result at run-time.- An example of how to use this routine is below: - PROGRAM bonds USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY : OUTPUT_UNIT USE LIBLAMMPS IMPLICIT NONE INTEGER(c_int), DIMENSION(:), ALLOCATABLE, TARGET :: bonds INTEGER(c_int), DIMENSION(:,:), POINTER :: bonds_array TYPE(lammps) :: lmp INTEGER :: i ! other commands to initialize LAMMPS, create bonds, etc. CALL lmp%gather_bonds(bonds) bonds_array(1:3, 1:SIZE(bonds)/3) => bonds DO i = 1, SIZE(bonds)/3 WRITE(OUTPUT_UNIT,'(A,1X,I4,A,I4,1X,I4)') 'bond', bonds_array(1,i), & '; type = ', bonds_array(2,i), bonds_array(3,i) END DO END PROGRAM bonds - Parameters:
- data [integer(kind=*),allocatable] :: array into which to copy the result. *The - KINDparameter is either- c_intor, if LAMMPS was compiled with- -DLAMMPS_BIGBIG, kind- c_int64_t.
- Call to:
 
- subroutine gather_angles(data)
- Gather type and constituent atom information for all angles. - New in version 8Feb2023. - This function copies the list of all angles into an allocatable array. The array will be filled with (angle type, angle atom 1, angle atom 2, angle atom 3) for each angle. The array is allocated to the right length (i.e., four times the number of angles). The array data must be of the same type as the LAMMPS - taginttype, which is equivalent to either- INTEGER(c_int)or- INTEGER(c_int64_t), depending on whether- -DLAMMPS_BIGBIGwas used when LAMMPS was built. If the supplied array does not match, an error will result at run-time.- An example of how to use this routine is below: - PROGRAM angles USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY : OUTPUT_UNIT USE LIBLAMMPS IMPLICIT NONE INTEGER(c_int), DIMENSION(:), ALLOCATABLE, TARGET :: angles INTEGER(c_int), DIMENSION(:,:), POINTER :: angles_array TYPE(lammps) :: lmp INTEGER :: i ! other commands to initialize LAMMPS, create angles, etc. CALL lmp%gather_angles(angles) angles_array(1:4, 1:SIZE(angles)/4) => angles DO i = 1, SIZE(angles)/4 WRITE(OUTPUT_UNIT,'(A,1X,I4,A,I4,1X,I4,1X,I4)') 'angle', angles_array(1,i), & '; type = ', angles_array(2,i), angles_array(3,i), angles_array(4,i) END DO END PROGRAM angles - Parameters:
- data [integer(kind=*),allocatable] :: array into which to copy the result. *The - KINDparameter is either- c_intor, if LAMMPS was compiled with- -DLAMMPS_BIGBIG, kind- c_int64_t.
- Call to:
 
- subroutine gather(self, name, count, data)
- Gather the named per-atom, per-atom fix, per-atom compute, or fix property/atom-based entities from all processes, in order by atom ID. - New in version 22Dec2022. - This subroutine gathers data from all processes and stores them in a one-dimensional allocatable array. The array data will be ordered by atom ID, which requires consecutive IDs (1 to natoms). If you need a similar array but for non-consecutive atom IDs, see - lammps_gather_concat(); for a similar array but for a subset of atoms, see- lammps_gather_subset().- The data array will be ordered in groups of count values, sorted by atom ID (e.g., if name is x, then data is [x(1,1), x(2,1), x(3,1), x(1,2), x(2,2), x(3,2), x(1,3), \(\dots\)]); data must be - ALLOCATABLEand will be allocated to length (count\({}\times{}\)natoms), as queried by- get_natoms().- This function will return an error if fix or compute data are requested and the fix or compute ID given does not have per-atom data. See the note about re-interpreting the vector as a matrix at - gather_atoms().- This function is not compatible with - -DLAMMPS_BIGBIG.- Parameters:
- name [character(len=*)] :: desired quantity (e.g., “x” or “mask” for atom properties, “f_id” for per-atom fix data, “c_id” for per-atom compute data, “d_name” or “i_name” for fix property/atom vectors with count = 1, “d2_name” or “i2_name” for fix property/atom vectors with count\({}> 1\)) 
- count [integer(c_int)] :: number of per-atom values (e.g., 1 for type or charge, 3 for x or f); use count = 3 with image if you want the image flags unpacked into (x,y,z) components. 
- data [real(c_double),dimension(:),allocatable] :: array into which to store the data. Array must have the - ALLOCATABLEattribute and be of rank 1 (i.e.,- DIMENSION(:)). If this array is already allocated, it will be reallocated to fit the length of the incoming data.
 
- Call to:
 
- subroutine gather_dihedrals(data)
- Gather type and constituent atom information for all dihedrals. - New in version 8Feb2023. - This function copies the list of all dihedrals into an allocatable array. The array will be filled with (dihedral type, dihedral atom 1, dihedral atom 2, dihedral atom 3, dihedral atom 4) for each dihedral. The array is allocated to the right length (i.e., five times the number of dihedrals). The array data must be of the same type as the LAMMPS - taginttype, which is equivalent to either- INTEGER(c_int)or- INTEGER(c_int64_t), depending on whether- -DLAMMPS_BIGBIGwas used when LAMMPS was built. If the supplied array does not match, an error will result at run-time.- An example of how to use this routine is below: - PROGRAM dihedrals USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY : OUTPUT_UNIT USE LIBLAMMPS IMPLICIT NONE INTEGER(c_int), DIMENSION(:), ALLOCATABLE, TARGET :: dihedrals INTEGER(c_int), DIMENSION(:,:), POINTER :: dihedrals_array TYPE(lammps) :: lmp INTEGER :: i ! other commands to initialize LAMMPS, create dihedrals, etc. CALL lmp%gather_dihedrals(dihedrals) dihedrals_array(1:5, 1:SIZE(dihedrals)/5) => dihedrals DO i = 1, SIZE(dihedrals)/5 WRITE(OUTPUT_UNIT,'(A,1X,I4,A,I4,1X,I4,1X,I4,1X,I4)') 'dihedral', dihedrals_array(1,i), & '; type = ', dihedrals_array(2,i), dihedrals_array(3,i), dihedrals_array(4,i), dihedrals_array(5,i) END DO END PROGRAM dihedrals - Parameters:
- data [integer(kind=*),allocatable] :: array into which to copy the result. *The - KINDparameter is either- c_intor, if LAMMPS was compiled with- -DLAMMPS_BIGBIG, kind- c_int64_t.
- Call to:
 
- subroutine gather_impropers(data)
- Gather type and constituent atom information for all impropers. - New in version 8Feb2023. - This function copies the list of all impropers into an allocatable array. The array will be filled with (improper type, improper atom 1, improper atom 2, improper atom 3, improper atom 4) for each improper. The array is allocated to the right length (i.e., five times the number of impropers). The array data must be of the same type as the LAMMPS - taginttype, which is equivalent to either- INTEGER(c_int)or- INTEGER(c_int64_t), depending on whether- -DLAMMPS_BIGBIGwas used when LAMMPS was built. If the supplied array does not match, an error will result at run-time.- An example of how to use this routine is below: - PROGRAM impropers USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY : OUTPUT_UNIT USE LIBLAMMPS IMPLICIT NONE INTEGER(c_int), DIMENSION(:), ALLOCATABLE, TARGET :: impropers INTEGER(c_int), DIMENSION(:,:), POINTER :: impropers_array TYPE(lammps) :: lmp INTEGER :: i ! other commands to initialize LAMMPS, create impropers, etc. CALL lmp%gather_impropers(impropers) impropers_array(1:5, 1:SIZE(impropers)/5) => impropers DO i = 1, SIZE(impropers)/5 WRITE(OUTPUT_UNIT,'(A,1X,I4,A,I4,1X,I4,1X,I4,1X,I4)') 'improper', impropers_array(1,i), & '; type = ', impropers_array(2,i), impropers_array(3,i), impropers_array(4,i), impropers_array(5,i) END DO END PROGRAM impropers - Parameters:
- data [integer(kind=*),allocatable] :: array into which to copy the result. *The - KINDparameter is either- c_intor, if LAMMPS was compiled with- -DLAMMPS_BIGBIG, kind- c_int64_t.
- Call to:
 
- subroutine gather_concat(self, name, count, data)
- Gather the named per-atom, per-atom fix, per-atom compute, or fix property/atom-based entities from all processes, unordered. - New in version 22Dec2022. - This subroutine gathers data for all atoms and stores them in a one-dimensional allocatable array. The data will be a concatenation of chunks from each processor’s owned atoms, in whatever order the atoms are in on each processor. This process has no requirement that the atom IDs be consecutive. If you need the ID of each atom, you can do another call to either - gather_atoms_concat()or- gather_concat()with name set to- id. If you have consecutive IDs and want the data to be in order, use- gather(); for a similar array but for a subset of atoms, use- gather_subset().- The data array will be in groups of count values, with natoms groups total, but not in order by atom ID (e.g., if name is x and count is 3, then data might be something like [x(1,11), x(2,11), x(3,11), x(1,3), x(2,3), x(3,3), x(1,5), \(\dots\)]); data must be - ALLOCATABLEand will be allocated to length (count \(\times\) natoms), as queried by- get_natoms().- This function is not compatible with - -DLAMMPS_BIGBIG.- Parameters:
- name [character(len=*)] :: desired quantity (e.g., “x” or “mask” for atom properties, “f_id” for per-atom fix data, “c_id” for per-atom compute data, “d_name” or “i_name” for fix property/atom vectors with count = 1, “d2_name” or “i2_name” for fix property/atom vectors with count\({}> 1\)) 
- count [integer(c_int)] :: number of per-atom values you expect per atom (e.g., 1 for type, mask, or charge; 3 for x, v, or f). Use count = 3 with image if you want a single image flag unpacked into x/y/z components. 
- data [polymorphic,dimension(:),allocatable] :: array into which to store the data. Array must have the - ALLOCATABLEattribute and be of rank 1 (i.e.,- DIMENSION(:)). If this array is already allocated, it will be reallocated to fit the length of the incoming data. It should have type- INTEGER(c_int)if expecting integer data and- REAL(c_double)if expecting floating-point data.
 
- Call to:
 
- subroutine gather_subset(name, count, ids, data)
- Gather the named per-atom, per-atom fix, per-atom compute, or fix property/atom-based entities from all processes for a subset of atoms. - New in version 22Dec2022. - This subroutine gathers data for the requested atom IDs and stores them in a one-dimensional allocatable array. The data will be ordered by atom ID, but there is no requirement that the IDs be consecutive. If you wish to return a similar array for all the atoms, use - gather()or- gather_concat().- The data array will be in groups of count values, sorted by atom ID in the same order as the array ids (e.g., if name is x, count = 3, and ids is [100, 57, 210], then data might look like [x(1,100), x(2,100), x(3,100), x(1,57), x(2,57), x(3,57), x(1,210), \(\dots\)]); ids must be provided by the user, and data must have the - ALLOCATABLEattribute and be of rank 1 (i.e.,- DIMENSION(:)). If data is already allocated, it will be reallocated to fit the length of the incoming data.- This function is not compatible with - -DLAMMPS_BIGBIG.- Parameters:
- name [character(len=*)] :: quantity to be scattered 
- ids [integer(c_int),dimension(:)] :: atom IDs corresponding to the atoms being scattered (e.g., “x” or “f” for atom properties, “f_id” for per-atom fix data, “c_id” for per-atom compute data, “d_name” or “i_name” for fix property/atom vectors with count = 1, “d2_name” or “i2_name” for fix property/atom vectors with count\({} > 1\)) 
- count [integer(c_int)] :: number of per-atom values you expect per atom (e.g., 1 for type, mask, or charge; 3 for x, v, or f). Use count = 3 with image if you want a single image flag unpacked into x/y/z components. 
- data [polymorphic,dimension(:),allocatable] :: per-atom values packed into a one-dimensional array containing the data to be scattered. This array must have the - ALLOCATABLEattribute and will be allocated either to the same length as ids (for mask, type, etc.) or to three times its length (for x, f, etc.); the array must be rank 1 and be of type- INTEGER(c_int)(e.g., for mask or type) or of type- REAL(c_double)(e.g., for charge, x, or f).
 
- Call to:
 
- subroutine scatter(name, data)
- This function calls - lammps_scatter()to scatter the named per-atom, per-atom fix, per-atom compute, or fix property/atom-based entity in data to all processes.- New in version 22Dec2022. - This subroutine takes data stored in a one-dimensional array supplied by the user and scatters them to all atoms on all processes. The data must be ordered by atom ID, with the requirement that the IDs be consecutive. Use - scatter_subset()to scatter data for some (or all) atoms, unordered.- The data array needs to be ordered in groups of count values, sorted by atom ID (e.g., if name is x and count = 3, then data = [x(1,1), x(2,1), x(3,1), x(1,2), x(2,2), x(3,2), x(1,3), \(\dots\)]); data must be of length (count \(\times\) natoms). - This function is not compatible with - -DLAMMPS_BIGBIG.- Parameters:
- name [character(len=*)] :: desired quantity (e.g., “x” or “f” for atom properties, “f_id” for per-atom fix data, “c_id” for per-atom compute data, “d_name” or “i_name” for fix property/atom vectors with count = 1, “d2_name” or “i2_name” for fix property/atom vectors with count\({} > 1\)) 
- data [polymorphic,dimension(:)] :: per-atom values packed in a one-dimensional array; data should be of type - INTEGER(c_int)or- REAL(c_double), depending on the type of data being scattered, and be of rank 1 (i.e.,- DIMENSION(:)).
 
- Call to:
 
- subroutine scatter_subset(name, ids, data)
- This function calls - lammps_scatter_subset()to scatter the named per-atom, per-atom fix, per-atom compute, or fix property/atom-based entities in data from a subset of atoms to all processes.- New in version 22Dec2022. - This subroutine takes data stored in a one-dimensional array supplied by the user and scatters them to a subset of atoms on all processes. The array data contains data associated with atom IDs, but there is no requirement that the IDs be consecutive, as they are provided in a separate array. Use - scatter()to scatter data for all atoms, in order.- The data array needs to be organized in groups of count values, with the groups in the same order as the array ids. For example, if you want data to be the array [x(1,1), x(2,1), x(3,1), x(1,100), x(2,100), x(3,100), x(1,57), x(2,57), x(3,57)], then count = 3 and ids = [1, 100, 57]. - This function is not compatible with - -DLAMMPS_BIGBIG.- Parameters:
- name [character(len=*)] :: desired quantity (e.g., “x” or “mask” for atom properties, “f_id” for per-atom fix data, “c_id” for per-atom compute data, “d_name” or “i_name” for fix property/atom vectors with count = 1, “d2_name” or “i2_name” for fix property/atom vectors with count\({}> 1\)) 
- ids [integer(c_int)] :: list of atom IDs to scatter data for 
- data [polymorphic ,dimension(:)] :: per-atom values packed in a one-dimensional array of length size(ids) * count. 
 
- Call to:
 
- subroutine create_atoms([id,] type, x, [v,] [image,] [bexpand])
- This method calls - lammps_create_atoms()to create additional atoms from a given list of coordinates and a list of atom types. Additionally, the atom IDs, velocities, and image flags may be provided.- New in version 3Nov2022. - Parameters:
- type [integer(c_int),dimension(N)] :: vector of \(N\) atom types (required/see note below) 
- x [real(c_double),dimension(3N)] :: vector of \(3N\ x/y/z\) positions of the new atoms, arranged as \([x_1,y_1,z_1,x_2,y_2,\dotsc]\) (required/see note below) 
 
- Options:
- id [integer(kind=*),dimension(N),optional] :: vector of \(N\) atom IDs; if absent, LAMMPS will generate them for you. *The - KINDparameter should be- c_intunless LAMMPS was compiled with- -DLAMMPS_BIGBIG, in which case it should be- c_int64_t.
- v [real(c_double),dimension(3N),optional] :: vector of \(3N\) x/y/z velocities of the new atoms, arranged as \([v_{1,x},v_{1,y},v_{1,z},v_{2,x}, \dotsc]\); if absent, they will be set to zero 
- image [integer(kind=*),dimension(N),optional] :: vector of \(N\) image flags; if absent, they are set to zero. *The - KINDparameter should be- c_intunless LAMMPS was compiled with- -DLAMMPS_BIGBIG, in which case it should be- c_int64_t. See note below.
- bexpand [logical,optional] :: if - .TRUE., atoms outside of shrink-wrap boundaries will be created, not dropped, and the box dimensions will be extended. Default is- .FALSE.
 
- Call to:
 - Note - The type and x arguments are required, but they are declared - OPTIONALin the module because making them mandatory would require id to be present as well. To have LAMMPS generate the ids for you, use a call something like- lmp%create_atoms(type=new_types, x=new_xs) - Note - When LAMMPS has been compiled with - -DLAMMPS_BIGBIG, it is not possible to include the image parameter but omit the id parameter. Either id must be present, or both id and image must be absent. This is required because having all arguments be optional in both generic functions creates an ambiguous interface. This limitation does not exist if LAMMPS was not compiled with- -DLAMMPS_BIGBIG.
- function find_pair_neighlist(style[, exact][, nsub][, reqid])
- Find index of a neighbor list requested by a pair style. - New in version 3Nov2022. - This function determines which of the available neighbor lists for pair styles matches the given conditions. It first matches the style name. If exact is - .TRUE., the name must match exactly; if- .FALSE., a regular expression or sub-string match is done. If the pair style is hybrid or hybrid/overlay, the style is matched against the sub-styles instead. If the same pair style is used multiple times as a sub-style, the nsub argument must be \(> 0\); this argument represents the nth instance of the sub-style (same as for the pair_coeff command, for example). In that case, nsub\({} = 0\) will not produce a match, and the function will return \(-1\).- The final condition to be checked is the request ID (reqid). This will usually be zero, but some pair styles request multiple neighbor lists and set the request ID to a value greater than zero. - Parameters:
- style [character(len=*)] :: String used to search for pair style instance. 
- Options:
- exact [logical,optional] :: Flag to control whether style should match exactly or only a regular expression/sub-string match is applied. Default: - .TRUE..
- nsub [integer(c_int),optional] :: Match nsubth hybrid sub-style instance of the same style. Default: 0. 
- reqid [integer(c_int),optional] :: Request ID to identify the neighbor list in case there are multiple requests from the same pair style instance. Default: 0. 
 
- Call to:
- Return:
- index [integer(c_int)] :: Neighbor list index if found, otherwise \(-1\). 
 
- function find_fix_neighlist(id[, reqid])
- Find index of a neighbor list requested by a fix. - New in version 3Nov2022. - The neighbor list request from a fix is identified by the fix ID and the request ID. The request ID is typically zero, but will be \(>0\) for fixes with multiple neighbor list requests. - Parameters:
- id [character(len=*)] :: Identifier of fix instance 
- Options:
- reqid [integer(c_int),optional] :: request ID to identify the neighbor list in cases in which there are multiple requests from the same fix. Default: 0. 
- Call to:
- Return:
- index [integer(c_int)] :: neighbor list index if found, otherwise \(-1\) 
 
- function find_compute_neighlist(id[, reqid])
- Find index of a neighbor list requested by a compute. - New in version 3Nov2022. - The neighbor list request from a compute is identified by the compute ID and the request ID. The request ID is typically zero, but will be \(> 0\) in case a compute has multiple neighbor list requests. - Parameters:
- id [character(len=*)] :: Identifier of compute instance. 
- Options:
- reqid [integer(c_int),optional] :: request ID to identify the neighbor list in cases in which there are multiple requests from the same compute. Default: 0. 
- Call to:
- Return:
- index [integer(c_int)] :: neighbor list index if found, otherwise \(-1\). 
 
- function neighlist_num_elements(idx)
- Return the number of entries in the neighbor list with the given index. - New in version 3Nov2022. - Parameters:
- idx [integer(c_int)] :: neighbor list index 
- Call to:
- lammps_neighlist_num_elements()- lammps_neighlist_num_elements()
- Return:
- inum [integer(c_int)] :: number of entries in neighbor list, or \(-1\) if idx is not a valid index. 
 
- subroutine neighlist_element_neighbors(idx, element, iatom, neighbors)
- Return atom local index, number of neighbors, and array of neighbor local atom indices of a neighbor list entry. - New in version 3Nov2022. - Parameters:
- idx [integer(c_int)] :: index of this neighbor list in the list of all neighbor lists 
- element [integer(c_int)] :: index of this neighbor list entry 
- iatom [integer(c_int)] :: local atom index (i.e., in the range [1,nlocal+nghost]; -1 if invalid or element value 
- neighbors [integer(c_int),dimension(:),pointer] :: pointer to an array of neighboring atom local indices 
 
- Call to:
 
- function version()
- This method returns the numeric LAMMPS version like - lammps_version()does.- Call to:
- Return:
- version [integer] :: LAMMPS version 
 
- subroutine get_os_info(buffer)
- This function can be used to retrieve detailed information about the hosting operating system and compiler/runtime environment. - New in version 3Nov2022. - A suitable buffer has to be provided. The assembled text will be truncated so as not to overflow this buffer. The string is typically a few hundred bytes long. - Parameters:
- buffer [character(len=*)] :: string that will house the information. 
- Call to:
 
- function config_has_mpi_support()
- This function is used to query whether LAMMPS was compiled with a real MPI library or in serial. - New in version 3Nov2022. - Call to:
- Return:
- has_mpi [logical] :: - .FALSE.when compiled with STUBS,- .TRUE.if complied with MPI.
 
- function config_has_gzip_support()
- Check if the LAMMPS library supports reading or writing compressed files via a pipe to gzip or similar compression programs. - New in version 3Nov2022. - Several LAMMPS commands (e.g., read_data command, write_data command, dump styles atom, custom, and xyz) support reading and writing compressed files via creating a pipe to the - gzipprogram. This function checks whether this feature was enabled at compile time. It does not check whether- gzipor any other supported compression programs themselves are installed and usable.- Call to:
- Return:
- has_gzip [logical] 
 
- function config_has_png_support()
- Check if the LAMMPS library supports writing PNG format images. - New in version 3Nov2022. - The LAMMPS dump style image supports writing multiple image file formats. Most of them, however, need support from an external library, and using that has to be enabled at compile time. This function checks whether support for the PNG image file format is available in the current LAMMPS library. - Call to:
- Return:
- has_png [logical] 
 
- function config_has_jpeg_support()
- Check if the LAMMPS library supports writing JPEG format images. - New in version 3Nov2022. - The LAMMPS dump style image supports writing multiple image file formats. Most of them, however, need support from an external library, and using that has to be enabled at compile time. This function checks whether support for the JPEG image file format is available in the current LAMMPS library. - Call to:
- Return:
- has_jpeg [logical] 
 
- function config_has_ffmpeg_support()
- Check if the LAMMPS library supports creating movie files via a pipe to ffmpeg. - New in version 3Nov2022. - The LAMMPS dump style movie supports generating movies from images on-the-fly via creating a pipe to the ffmpeg program. This function checks whether this feature was enabled at compile time. It does not check whether the - ffmpegitself is installed and usable.- Call to:
- Return:
- has_ffmpeg [logical] 
 
- function config_has_exceptions()
- Check whether LAMMPS errors will throw C++ exceptions. - New in version 3Nov2022. - When using the library interface, the library interface functions will “catch” exceptions, and then the error status can be checked by calling - has_error(). The most recent error message can be retrieved via- get_last_error_message(). This allows to restart a calculation or delete and recreate the LAMMPS instance when a C++ exception occurs. One application of using exceptions this way is the LAMMPS shell.- Call to:
- Return:
- has_exceptions [logical] 
 
- function config_has_package(name)
- Check whether a specific package has been included in LAMMPS - New in version 3Nov2022. - This function checks whether the LAMMPS library in use includes the specific LAMMPS package provided as argument. - Call to:
- Return:
- has_package [logical] 
 
- function config_package_count()
- Count the number of installed packages in the LAMMPS library. - New in version 3Nov2022. - This function counts how many LAMMPS packages are included in the LAMMPS library in use. It directly calls the C library function - lammps_config_package_count().- Call to:
- Return:
- npackages [integer(c_int)] :: number of packages installed 
 
- subroutine config_package_name(idx, buffer)
- Get the name of a package in the list of installed packages in the LAMMPS library. - New in version 3Nov2022. - This subroutine copies the name of the package with the index idx into the provided string buffer. If the name of the package exceeds the length of the buffer, it will be truncated accordingly. If the index is out of range, buffer is set to an empty string. - Parameters:
- idx [integer(c_int)] :: index of the package in the list of included packages \((0 \le idx < \text{package count})\) 
- buffer [character(len=*)] :: string to hold the name of the package 
 
- Call to:
 
- subroutine installed_packages(package[, length])
- Obtain a list of the names of enabled packages in the LAMMPS shared library and store it in package. - New in version 3Nov2022. - This function is analogous to the - installed_packagesfunction in the Python API. The optional argument length sets the length of each string in the vector package (default: 31).- Parameters:
- package [character(len=:),dimension(:),allocatable] :: list of packages; must have the - ALLOCATABLEattribute and be of rank 1 (i.e.,- DIMENSION(:)) with allocatable length.
- Options:
- length [integer,optional] :: length of each string in the list. Default: 31. 
- Call to:
 
- function config_accelerator(package, category, setting)
- This function calls - lammps_config_accelerator()to check the availability of compile time settings of included accelerator packages in LAMMPS.- New in version 3Nov2022. - Supported packages names are “GPU”, “KOKKOS”, “INTEL”, and “OPENMP”. Supported categories are “api” with possible settings “cuda”, “hip”, “phi”, “pthreads”, “opencl”, “openmp”, and “serial”; and “precision” with possible settings “double”, “mixed”, and “single”. - Parameters:
- package [character(len=*)] :: string with the name of the accelerator package 
- category [character(len=*)] :: string with the name of the setting 
- setting [character(len=*)] :: string with the name of the specific setting 
 
- Call to:
- Return:
- available [logical] :: - .TRUE.if the combination of package, category, and setting is available, otherwise- .FALSE..
 
- function has_gpu_device()
- Checks for the presence of a viable GPU package device. - New in version 3Nov2022. - This function calls - lammps_has_gpu_device(), which checks at runtime whether an accelerator device is present that can be used with the GPU package.- More detailed information about the available device or devices can be obtained by calling the - get_gpu_device_info()subroutine.- Call to:
- Return:
- available [logical] :: - .TRUE.if a viable device is available,- .FALSE.if not.
 
- subroutine get_gpu_device_info(buffer)
- Get GPU package device information. - New in version 3Nov2022. - Calls - lammps_get_gpu_device_info()to retrieve detailed information about any accelerator devices that are viable for use with the GPU package. It will fill buffer with a string that is equivalent to the output of the- nvc_get_deviceor- ocl_get_deviceor- hip_get_devicetools that are compiled alongside LAMMPS if the GPU package is enabled.- A suitable-length Fortran string has to be provided. The assembled text will be truncated so as not to overflow this buffer. This string can be several kilobytes long if multiple devices are present. - Parameters:
- buffer [character(len=*)] :: string into which to copy the information. 
- Call to:
 
- function has_style(category, name)
- Check whether a specific style has been included in LAMMPS. - New in version 3Nov2022. - This function calls - lammps_has_style()to check whether the LAMMPS library in use includes the specific style name associated with a specific category provided as arguments. Please see- lammps_has_style()for a list of valid categories.- Parameters:
- category [character(len=*)] :: category of the style 
- name [character(len=*)] :: name of the style 
 
- Call to:
- Return:
- has_style [logical] :: - .TRUE.if included,- .FALSE.if not.
 
- function style_count(category)
- Count the number of styles of category in the LAMMPS library. - New in version 3Nov2022. - This function counts how many styles in the provided category are included in the LAMMPS library currently in use. Please see - lammps_has_style()for a list of valid categories.- Parameters:
- category [character(len=*)] :: category of styles to count 
- Call to:
- Return:
- count [integer(c_int)] :: number of styles in category 
 
- subroutine style_name(category, idx, buffer)
- Look up the name of a style by index in the list of styles of a given category in the LAMMPS library. - New in version 3Nov2022. - This function calls - lammps_style_name()and copies the name of the category style with index idx into the provided string buffer. The length of buffer must be long enough to contain the name of the style; if it is too short, the name will be truncated accordingly. If idx is out of range, buffer will be the empty string and a warning will be issued.- Parameters:
- category [character(len=*)] :: category of styles 
- idx [integer(c_int)] :: index of the style in the list of category styles \((1 \leq idx \leq \text{style count})\) 
- buffer [character(len*)] :: string buffer to copy the name of the style into 
 
- Call to:
 
- function has_id(category, name)
- This function checks if the current LAMMPS instance a category ID of the given name exists. Valid categories are: compute, dump, fix, group, molecule, region, and variable. - New in version 3Nov2022. - Parameters:
- category [character(len=*)] :: category of the ID 
- name [character(len=*)] :: name of the ID 
 
- Call to:
- Return:
- has_id [logical] :: - .TRUE.if category style name exists,- .FALSE.if not.
 
- function id_count(category)
- This function counts how many IDs in the provided category are defined in the current LAMMPS instance. Please see - has_id()for a list of valid categories.- New in version 3Nov2022. - Parameters:
- category [character(len=*)] :: category of the ID 
- Call to:
- Return:
- count [integer(c_int)] :: number of IDs in category 
 
- subroutine id_name(category, idx, buffer)
- Look up the name of an ID by index in the list of IDs of a given category. - New in version 3Nov2022. - This function copies the name of the category ID with the index idx into the provided string buffer. The length of the buffer must be long enough to hold the string; if the name of the style exceeds the length of the buffer, it will be truncated accordingly. If buffer is - ALLOCATABLE, it must be allocated before the function is called. If idx is out of range, buffer is set to an empty string and a warning is issued.- Parameters:
- category [character(len=*)] :: category of IDs 
- idx [integer(c_int)] :: index of the ID in the list of category styles (\(0 \leq idx < count\)) 
- buffer [character(len=*)] :: string into which to copy the name of the style 
 
- Call to:
 
- function plugin_count()
- This function counts the number of loaded plugins. - New in version 3Nov2022. - Call to:
- lammps_plugin_count()
- Return:
- n [integer(c_int)] :: number of loaded plugins 
 
- subroutine plugin_name(idx, stylebuf, namebuf)
- Look up the style and name of a plugin by its index in the list of plugins. - New in version 3Nov2022. - This function copies the name of the style plugin with the index idx into the provided C-style string buffer. The length of the buffer must be provided as buf_size argument. If the name of the style exceeds the length of the buffer, it will be truncated accordingly. If the index is out of range, both strings are set to the empty string and a warning is printed. - Parameters:
- idx [integer(c_int)] :: index of the plugin in the list all or style plugins 
- stylebuf [character(len=*)] :: string into which to copy the style of the plugin 
- namebuf [character(len=*)] :: string into which to copy the style of the plugin 
 
- Call to:
- lammps_plugin_name()
 
- function encode_image_flags(ix, iy, iz)
- Encodes three integer image flags into a single imageint. - New in version 3Nov2022. - This function performs the bit-shift, addition, and bit-wise OR operations necessary to combine the values of three integers representing the image flags in the \(x\)-, \(y\)-, and \(z\)-directions. Unless LAMMPS is compiled with - -DLAMMPS_BIGBIG, those integers are limited to 10-bit signed integers \([-512,512)\). If- -DLAMMPS_BIGBIGwas used when compiling, then the return value is of kind- c_int64_tinstead of kind- c_int, and the valid range for the individual image flags becomes \([-1048576,1048575)\) (i.e., the range of a 21-bit signed integer). There is no check on whether the arguments conform to these requirements; values out of range will simply be wrapped back into the interval.- Parameters:
- ix [integer(c_int)] :: image flag in \(x\)-direction 
- iy [integer(c_int)] :: image flag in \(y\)-direction 
- iz [integer(c_int)] :: image flag in \(z\)-direction 
 
- Return:
- imageint [integer(kind=*)] :: encoded image flag. *The - KINDparameter is- c_intunless LAMMPS was built with- -DLAMMPS_BIGBIG, in which case it is- c_int64_t.
 - Note - The fact that the programmer does not know the - KINDparameter of the return value until compile time means that it is impossible to define an interface that works for both sizes of- imageint. One side effect of this is that you must assign the return value of this function to a variable; it cannot be used as the argument to another function or as part of an array constructor. For example,- my_images = [lmp%encode_image_flags(0,0,0), lmp%encode_image_flags(1,0,0)] - will not work; instead, do something like - my_images(1) = lmp%encode_image_flags(0,0,0) my_images(2) = lmp%encode_image_flags(1,0,0) 
- subroutine decode_image_flags(image, flags)
- This function does the reverse operation of - encode_image_flags(): it takes the image flag and performs the bit-shift and bit-masking operations to decode it and stores the resulting three integers into the array flags.- New in version 3Nov2022. - Parameters:
- image [integer(kind=*)] :: encoded image flag. *The - KINDparameter is either- c_intor, if LAMMPS was compiled with- -DLAMMPS_BIGBIG,- c_int64_t. Kind compatibility is checked at run-time.
- flags [integer(c_int),dimension(3)] :: three-element vector where the decoded image flags will be stored. 
 
 
- subroutine set_fix_external_callback(id, callback, caller)
- Set the callback function for a fix external instance with the given ID. - New in version 22Dec2022. - Fix external allows programs that are running LAMMPS through its library interface to modify certain LAMMPS properties on specific time steps, similar to the way other fixes do. - This subroutine sets the callback function for use with the “pf/callback” mode. The function should have Fortran language bindings with the following interface, which depends on how LAMMPS was compiled: - ABSTRACT INTERFACE SUBROUTINE external_callback(caller, timestep, ids, x, fexternal) USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int, c_double, c_int64_t CLASS(*), INTENT(INOUT) :: caller INTEGER(c_bigint), INTENT(IN) :: timestep INTEGER(c_tagint), DIMENSION(:), INTENT(IN) :: ids REAL(c_double), DIMENSION(:,:), INTENT(IN) :: x REAL(c_double), DIMENSION(:,:), INTENT(OUT) :: fexternal END SUBROUTINE external_callback END INTERFACE - where - c_bigintis- c_intif- -DLAMMPS_SMALLSMALLwas used and- c_int64_totherwise; and- c_tagintis- c_int64_tif- -DLAMMPS_BIGBIGwas used and- c_intotherwise.- The argument caller to - set_fix_external_callback()is unlimited polymorphic (i.e., it can be any Fortran object you want to pass to the calling function) and will be available as the first argument to the callback function. It can be your LAMMPS instance, which you might need if the callback function needs access to the library interface. The argument must be a scalar; to pass non-scalar data, wrap those data in a derived type and pass an instance of the derived type to caller.- The array ids is an array of length nlocal (as accessed from the - Atomclass or through- extract_global()). The arrays x and fexternal are \(3 \times {}\)nlocal arrays; these are transposed from what they would look like in C (see note about array index order at- extract_atom()).- The callback mechanism is one of two ways that forces can be applied to a simulation with the help of fix external. The alternative is array mode, where one calls - fix_external_get_force().- Please see the documentation for fix external for more information about how to use the fix and couple it with external programs. - Parameters:
- id [character(len=*)] :: ID of fix external instance 
- callback [external] :: subroutine fix external should call 
- caller [class(*),optional] :: object you wish to pass to the callback procedure (must be a scalar; see note) 
 
- Call to:
 - Note - The interface for your callback function must match types precisely with the abstract interface block given above. The compiler probably will not be able to check this for you. In particular, the first argument (“caller”) must be of type - CLASS(*)or you will probably get a segmentation fault or at least a misinterpretation of whatever is in memory there. You can resolve the object using the- SELECT TYPEconstruct. An example callback function (assuming LAMMPS was compiled with- -DLAMMPS_SMALLBIG) that applies something akin to Hooke’s Law (with each atom having a different k value) is shown below.- MODULE stuff USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int, c_double, c_int64_t USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY : error_unit IMPLICIT NONE TYPE shield REAL(c_double), DIMENSION(:,:), ALLOCATABLE :: k ! assume k gets allocated to dimension(3,nlocal) at some point ! and assigned values END TYPE shield SUBROUTINE my_callback(caller, timestep, ids, x, fexternal) CLASS(*), INTENT(INOUT) :: caller INTEGER(c_int), INTENT(IN) :: timestep INTEGER(c_int64_t), INTENT(IN) :: ids REAL(c_double), INTENT(IN) :: x(:,:) REAL(c_double), INTENT(OUT) :: fexternal(:,:) SELECT TYPE (caller) TYPE IS (shield) fexternal = - caller%k * x CLASS DEFAULT WRITE(error_unit,*) 'UH OH...' END SELECT END SUBROUTINE my_callback END MODULE stuff ! then, when assigning the callback function, do this: PROGRAM example USE LIBLAMMPS USE stuff TYPE(lammps) :: lmp TYPE(shield) :: my_shield lmp = lammps() CALL lmp%command('fix ext all external pf/callback 1 1') CALL lmp%set_fix_external_callback('ext', my_callback, my_shield) END PROGRAM example 
- function fix_external_get_force(id)
- Get pointer to the force array storage in a fix external instance with the given ID. - New in version 22Dec2022. - Fix external allows programs that are running LAMMPS through its library interfaces to add or modify certain LAMMPS properties on specific time steps, similar to the way other fixes do. - This function provides access to the per-atom force storage in a fix external instance with the given fix-ID to be added to the individual atoms when using the “pf/array” mode. The fexternal array can be accessed like other “native” per-atom arrays accessible via the - extract_atom()function. Please note that the array stores the forces for local atoms for each MPI rank, in the order determined by the neighbor list build. Because the underlying data structures can change as well as the order of atom as they migrate between MPI processes because of the domain decomposition parallelization, this function should be always called immediately before the forces are going to be set to get an up-to-date pointer. You can use, for example,- extract_setting()to obtain the number of local atoms nlocal and then assume the dimensions of the returned force array as- REAL(c_double) :: force(3,nlocal).- This function is an alternative to the callback mechanism in fix external set up by - set_fix_external_callback(). The main difference is that this mechanism can be used when forces are to be pre-computed and the control alternates between LAMMPS and the external driver, while the callback mechanism can call an external subroutine to compute the force when the fix is triggered and needs them.- Please see the documentation for fix external for more information about how to use the fix and how to couple it with an external program. - Parameters:
- id [character(len=*)] :: ID of fix external instance 
- Call to:
- Return:
- fexternal [real(c_double),dimension(3,nlocal)] :: pointer to the per-atom force array allocated by the fix 
 
- subroutine fix_external_set_energy_global(id, eng)
- Set the global energy contribution for a fix external instance with the given ID. - New in version 22Dec2022. - This is a companion function to - set_fix_external_callback()and- fix_external_get_force()that also sets the contribution to the global energy from the external program. The value of the eng argument will be stored in the fix and applied on the current and all following time steps until changed by another call to this function. The energy is in energy units as determined by the current units settings and is the total energy of the contribution. Thus, when running in parallel, all MPI processes have to call this function with the same value, and this will be returned as a scalar property of the fix external instance when accessed in LAMMPS input commands or from variables.- Please see the documentation for fix external for more information about how to use the fix and how to couple it with an external program. - Parameters:
- id [character(len=*)] :: fix ID of fix external instance 
- eng [real(c_double)] :: total energy to be added to the global energy 
 
- Call to:
 
- subroutine fix_external_set_virial_global(id, virial)
- Set the global virial contribution for a fix external instance with the given ID. - New in version 22Dec2022. - This is a companion function to - set_fix_external_callback()and- fix_external_get_force()to set the contribution to the global virial from an external program.- The six values of the virial array will be stored in the fix and applied on the current and all following time steps until changed by another call to this function. The components of the virial need to be stored in the following order: xx, yy, zz, xy, xz, yz. In LAMMPS, the virial is stored internally as stress*volume in units of pressure*volume as determined by the current units settings and is the total contribution. Thus, when running in parallel, all MPI processes have to call this function with the same value, and this will then be added by fix external. - Please see the documentation for fix external for more information about how to use the fix and how to couple it with an external code. - Parameters:
- id [character(len=*)] :: fix ID of fix external instance 
- virial [real(c_double),dimension(6)] :: the six global stress tensor components to be added to the global virial 
 
- Call to:
 
- subroutine fix_external_set_energy_peratom(id, eng)
- Set the per-atom energy contribution for a fix external instance with the given ID. - New in version 22Dec2022. - This is a companion function to - set_fix_external_callback()to set the per-atom energy contribution due to the fix from the external program as part of the callback function. For this to work, the LAMMPS object must be passed as part of the caller argument when registering the callback function, or the callback function must otherwise have access to the LAMMPS object, such as through a module-based pointer.- Note - This function is fully independent from - fix_external_set_energy_global()and will NOT add any contributions to the global energy tally and will NOT check whether the sum of the contributions added here are consistent with the global added energy.- Please see the documentation for fix external for more information about how to use the fix and how to couple it with an external code. - Parameters:
- id [character(len=*)] :: fix ID of the fix external instance 
- eng [real(c_double),dimension(:)] :: array of length nlocal containing the energy to add to the per-atom energy 
 
- Call to:
 
- subroutine set_fix_external_set_virial_peratom(id, virial)
- This is a companion function to - set_fix_external_callback()to set the per-atom virial contribution due to the fix from the external program as part of the callback function. For this to work, the LAMMPS object must be passed as the caller argument when registering the callback function.- New in version 22Dec2022. - Note - This function is fully independent from - fix_external_set_virial_global()and will NOT add any contributions to the global virial tally and NOT check whether the sum of the contributions added here are consistent with the global added virial.- The order and units of the per-atom stress tensor elements are the same as for the global virial. The type and dimensions of the per-atom virial array must be - REAL(c_double), DIMENSION(6,nlocal).- Please see the documentation for fix external for more information about how to use the fix and how to couple it with an external program. - Parameters:
- id [character(len=*)] :: fix ID of fix external instance 
- virial [real(c_double),dimension(:,:)] :: an array of \(6 \times{}\)nlocal components to be added to the per-atom virial 
 
- Call to:
- lammps_set_virial_peratom()
 
- subroutine fix_external_set_vector_length(id, length)
- Set the vector length for a global vector stored with fix external for analysis. - New in version 22Dec2022. - This is a companion function to - set_fix_external_callback()and- fix_external_get_force()to set the length of a global vector of properties that will be stored with the fix via- fix_external_set_vector().- This function needs to be called before a call to - fix_external_set_vector()and before a run or minimize command. When running in parallel, it must be called from all MPI processes with the same length argument.- Please see the documentation for fix external for more information about how to use the fix and how to couple it with an external program. - Parameters:
- id [character(len=*)] :: fix ID of fix external instance 
- length [integer(c_int)] :: length of the global vector to be stored with the fix 
 
- Call to:
 
- subroutine fix_external_set_vector(id, idx, val)
- Store a global vector value for a fix external instance with the given ID. - New in version 22Dec2022. - This is a companion function to - set_fix_external_callback()and- fix_external_get_force()to set the values of a global vector of properties that will be stored with the fix and can be accessed from within LAMMPS input commands (e.g., fix ave/time or variables) when used in a vector context.- This function needs to be called after a call to - fix_external_set_vector_length()and before a run or minimize command. When running in parallel, it must be called from all MPI processes with the same idx and val parameters. The variable val is assumed to be extensive.- Note - The index in the idx parameter is 1-based (i.e., the first element is set with idx\({} = 1\), and the last element of the vector with idx\({} = N\), where \(N\) is the value of the length parameter of the call to - fix_external_set_vector_length()).- Please see the documentation for fix external for more information about how to use the fix and how to couple it with an external code. - Parameters:
- id [character(len=*)] :: ID of fix external instance 
- idx [integer(c_int)] :: 1-based index in global vector 
- val [integer(c_int)] :: value to be stored in global vector at index idx 
 
- Call to:
 
- subroutine flush_buffers()
- This function calls - lammps_flush_buffers(), which flushes buffered output to be written to screen and logfile. This can simplify capturing output from LAMMPS library calls.- New in version 3Nov2022. - Call to:
 
- function is_running()
- Check if LAMMPS is currently inside a run or minimization. - New in version 3Nov2022. - This function can be used from signal handlers or multi-threaded applications to determine if the LAMMPS instance is currently active. - Call to:
- Return:
- is_running [logical] :: - .FALSE.if idle or- .TRUE.if active
 
- subroutine force_timeout()
- Force a timeout to stop an ongoing run cleanly. - New in version 3Nov2022. - This function can be used from signal handlers or multi-threaded applications to terminate an ongoing run cleanly. - Call to:
 
- function has_error()
- Check if there is a (new) error message available. - New in version 3Nov2022. - This function can be used to query if an error inside of LAMMPS has thrown a C++ exception. - Call to:
- Return:
- has_error [logical] :: - .TRUE.if there is an error.
 
- subroutine get_last_error_message(buffer[, status])
- Copy the last error message into the provided buffer. - New in version 3Nov2022. - This function can be used to retrieve the error message that was set in the event of an error inside of LAMMPS that resulted in a C++ exception. A suitable buffer for a string has to be provided. If the internally-stored error message is longer than the string, it will be truncated accordingly. The optional argument status indicates the kind of error: a “1” indicates an error that occurred on all MPI ranks and is often recoverable, while a “2” indicates an abort that would happen only in a single MPI rank and thus may not be recoverable, as other MPI ranks may be waiting on the failing MPI rank(s) to send messages. - Parameters:
- buffer [character(len=*)] :: string buffer to copy the error message into 
- Options:
- status [integer(c_int),optional] :: 1 when all ranks had the error, 2 on a single-rank error. 
- Call to:
 
