Fortran interface reference

The chemfiles module is built around the main types of chemfiles: chfl_trajectory, chfl_frame, chfl_cell, chfl_topology, chfl_residue, chfl_atom and chfl_selection. For more information about these types, please see the chemfiles overview.

Warning

Atomic indexes in chemfiles starts at 0, not 1. That means that the first atom in a frame have the index 0, not 1. This should be taken in account when using chemfiles functions. Fortran arrays returned by function still have indexes starting at 1.

program indexing
    use iso_fortran_env, only: real64, int64
    use chemfiles
    implicit none
    type(chfl_frame)      :: frame
    type(chfl_atom)       :: atom
    real(real64), pointer :: positions(:, :)
    integer(int64)        :: natoms

    ! Initialize the frame ...

    ! Get the first atom in the frame
    call atom%from_frame(frame, 0)
    ! Get the second atom in the frame
    call atom%from_frame(frame, 1)

    call frame%poositions(positions, natoms)
    ! position(1, :) now contains the positions of the first atom
end program

Conventions

All the functions and types have the chfl_ prefix. All the functions take an optional status argument which will indicate the status of the operation. It should be CHFL_SUCCESS if everything was OK, and another value indicating in case of error. The only exeption to this rule are the functions returnning character strings: chfl_version and chfl_last_error().

When creating a variable of one of the chemfiles types, the first routine to be called should be an initialization routine. It can be either the init routine for default initialization, or another routine documented as initializing.

type(chfl_cell) :: cell
type(chfl_frame) :: frame

! Initialize the variables
call cell%init([20, 20, 20])
call frame%init()

! free the memory
call cell%free()
call frame%free()

These initialization function should only be called once. In order to free the memory asssociated with any chemfiles variable, the free subroutine should be called. After a call the the free subroutine, the init subroutine can be called again whithout any memory leak risk. Not initializing chemfiles variables will lead to errors.

Error and logging functions

function chfl_version()

Get the version of the Chemfiles library.

Return:character [len=*] :: chemfiles version
function chfl_last_error()

Get the last error message emmited by Chemfiles.

Return:character [len=*] :: error message for the last error
subroutine chfl_clear_errors([status])

Clear the last error message emmited by Chemfiles.

Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_set_warning_callback(callback[, status])

Chemfiles sends warning on various events, for example invalid files or errors in the API usage. By default they are printed to the standard error stream, but you can redirect them by setting a callback to be called on each event with the event message. This function set the callback for all warning events.

Parameters:callback [procedure,kind=chfl_warning_callback] :: warning callback
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_warning_callback(message)

Interface for the warning callback to be used with chfl_set_warning_callback.

Parameters:message [character,len=*, intent(in)] :: The warning message

The optional status argument is an integer of kind chfl_status, which can take the following values:

integer(chfl_status) :: CHFL_SUCCESS

Status for successful operations.

integer(chfl_status) :: CHFL_MEMORY_ERROR

Status code for error concerning memory: out of memory, wrong size for pre-allocated buffers, etc.

integer(chfl_status) :: CHFL_FILE_ERROR

Status code for error concerning files: the file do not exist, the user does not have rights to open it, etc.

integer(chfl_status) :: CHFL_FORMAT_ERROR

Status code for error in file formating, i.e. for invalid files.

integer(chfl_status) :: CHFL_SELECTION_ERROR

Status code for invalid selection strings.

integer(chfl_status) :: CHFL_GENERIC_ERROR

Status code for any other error from Chemfiles.

integer(chfl_status) :: CHFL_CXX_ERROR

Status code for error in the C++ standard library.

chfl_trajectory type

type chfl_trajectory

The chfl_trajectory type is the main entry point when using chemfiles. A chfl_trajectory behave a like a file, allowing to read and/or write chfl_frame.

The initialization routine for chfl_trajectory are chfl_trajectory%open() and chfl_trajectory%with_format(). The memory liberation routine is chfl_trajectory%close().

Type fields:
subroutine chfl_trajectory%open(path, mode[, status])

Open the file at the given path using the given mode. Valid modes are 'r' for read, 'w' for write and 'a' for append.

Parameters:
  • path [character,len=*] :: path to the trajectory file
  • mode [character] :: opening mode
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_trajectory%with_format(path, mode, format[, status])

Open the trajectory at the given path using a specific file format and the given mode.

This is be needed when the file format does not match the extension, or when there is not standard extension for this format. Valid modes are 'r' for read, 'w' for write and 'a' for append.

If format is an empty string, the format will be guessed from the extension.

Parameters:
  • path [character,len=*] :: path to the trajectory file
  • mode [character] :: opening mode
  • format [character,len=*] :: format to use
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_trajectory%read(frame[, status])

Read the next step of the trajectory into a frame.

If the number of atoms in frame does not correspond to the number of atom in the next step, the frame is resized.

Parameters:frame [chfl_frame] :: frame to fill with the data
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_trajectory%read_step(step, frame[, status])

Read a specific step of the trajectory into a frame. The first trajectory step is the step 0.

If the number of atoms in frame does not correspond to the number of atom in the step, the frame is resized.

Parameters:
  • step [integer] :: step to read
  • frame [chfl_frame] :: frame to fill with the data
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_trajectory%write(frame[, status])

Write a single frame to the trajectory.

Parameters:frame [chfl_frame] :: frame to be writen to the file
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_trajectory%set_topology(topology[, status])

Set the topology associated with the trajectory. This topology will be used when reading and writing the files, replacing any topology in the frames or files.

Parameters:topology [chfl_topology] :: new topology to use
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_trajectory%topology_file(path[, format, status])

Set the topology associated with the trajectory by reading the first frame of the file at the given path using the file format in format; and extracting the topology of this frame.

If format is an empty string or not given, the format will be guessed from the extension.

Parameters:

path [character,len=*] :: file to read in order to get the new topology

Options:
  • format [string,optional] :: format to use for the topology file
  • status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_trajectory%set_cell(cell[, status])

Set the unit cell associated with the trajectory. This cell will be used when reading and writing the files, replacing any pre-existing unit cell.

Parameters:cell [chfl_cell] :: new cell to use
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_trajectory%nsteps(nsteps[, status])

Store the number of steps (the number of frames) from the trajectory in nsteps.

Parameters:nsteps [integer] :: number of steps
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_trajectory%close([status])

Close a trajectory file, and free the associated memory.

Closing a file will synchronize all changes made to the file with the storage (hard drive, network, …) used for this file.

Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

chfl_frame type

type chfl_frame

A chfl_frame contains data from one simulation step: the current unit cell, the topology, the positions, and the velocities of the particles in the system. If some information is missing (topology or velocity or unit cell), the corresponding data is filled with a default value.

The initialization routine for chfl_frame are chfl_frame%init() and chfl_frame%copy().

Type fields:
subroutine chfl_frame%init([status])

Initialize this unit cell with a new empty frame. It will be resized by the library as needed.

Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_frame%copy(frame[, status])

Initialize this frame with a copy of frame.

Parameters:frame [chfl_frame] :: frame to copy
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_frame%atoms_count(natoms[, status])

Get the current number of atoms in the frame in natoms.

Parameters:natoms [integer] :: number of atoms in the frame
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_frame%add_atom(atom, position[, velocity, status])

Add a chfl_atom and the corresponding position and velocity data to this frame. velocity can be absent if no velocity is associated with this frame.

Parameters:
  • atom [chfl_atom] :: atom to add to the frame
  • position (3) [real] :: atom position
Options:
  • velocity (3) [real,optional] :: atom velocity
  • status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_frame%remove(index[, status])

Remove the atom at the given index in the frame.

This modify all the atoms indexes after index, and invalidate any pointer obtained using chfl_frame%positions() or chfl_frame%velocities().

Parameters:index [integer] :: index of the atom to remove
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_frame%resize(natoms[, status])

Resize the positions, velocities and topology in the frame, to have space for natoms atoms.

This function may invalidate any pointer to the positions or the velocities if the new size is bigger than the old one. In all the cases, previous data is conserved. This function conserve the presence or absence of velocities.

Parameters:natoms [integer] :: the new number of atoms in the frame
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_frame%positions(data, size[, status])

Get a pointer to the positions array from the frame.

This function set the data array to be the internal positions array. This array is a natoms x 3 array, and the number of atoms will be in the size parameter.

This function gives access to chemfiles internal data structure, and do not perform any copy, both when reading and writing the positions.

If the frame is resized (by writing to it, or calling chfl_frame%resize()), the pointer is invalidated. If the frame is freed using chfl_frame%free(), the pointer is freed too.

Parameters:
  • data (*, *) [real,pointer] :: pointer to a float array containing the positions
  • size [integer] :: number of atom, i.e. size of the data array
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_frame%velocities(data, size[, status])

Get a pointer to the velocities array from the frame.

This function set the data array to be the internal positions array. This array is a natoms x 3 array, and the number of atoms will be in the size parameter.

This function gives access to chemfiles internal data structure, and do not perform any copy, both when reading and writing the velocities.

If the frame is resized (by writing to it, or calling chfl_frame%resize()), the pointer is invalidated. If the frame is freed using chfl_frame%free(), the pointer is freed too.

Parameters:
  • data (*, *) [real,pointer] :: pointer to a float array containing the velocities
  • size [integer] :: number of atom, i.e. size of the data array
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_frame%add_velocities([status])

Add velocity data to this frame.

The velocities ar initialized to zero. If the frame already has velocities, this does nothing.

Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_frame%has_velocities(result[, status])

Check if this frame contains velocity data.

Parameters:result [logical,kind=1] :: .true. if the frame has velocities, .false. otherwise.
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_frame%set_cell(cell[, status])

Set the chfl_cell of this frame to cell.

Parameters:cell [chfl_cell] :: new unit cell of the frame
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_frame%set_topology(topology[, status])

Set the chfl_topology of this frame to topology.

Calling this function with a topology that does not contain the right number of atom will return an error.

Parameters:topology [chfl_topology] :: new topology of the frame
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_frame%step(step[, status])

Get the frame step, i.e. the frame number in the trajectory in step.

Parameters:step [integer] :: frame step number
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_frame%set_step(step[, status])

Set the frame step, i.e. the frame number in the trajectory to step.

Parameters:step [integer] :: The new frame step
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_frame%guess_topology([status])

Guess the bonds, angles and dihedrals in the frame.

The bonds are guessed using a distance-based algorithm, and then angles and dihedrals are guessed from the bonds.

Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_frame%free([status])

Destroy a frame, and free the associated memory

Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

chfl_cell type

type chfl_cell

A chfl_cell represent the box containing the atoms, and its periodicity.

An unit cell is fully represented by three lengths (a, b, c); and three angles (alpha, beta, gamma). The angles are stored in degrees, and the lengths in Angstroms.

The initialization routine for chfl_cell are chfl_cell%init(), chfl_cell%triclinic(), chfl_cell%from_frame() and chfl_cell%copy().

Type fields:
subroutine chfl_cell%init(lengths[, status])

Initialize this unit cell with an unit cell having the given lengths. The unit cell shape is CHFL_CELL_ORTHORHOMBIC.

Parameters:lengths (3) [real] :: cell lengths, in angstroms
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_cell%triclinic(lengths, angles[, status])

Initialize this unit cell with an unit cell having the given lengths and angles. The unit cell shape is CHFL_CELL_TRICLINIC.

Parameters:
  • lengths (3) [real] :: cell lengths, in angstroms
  • angles (3) [real] :: cell angles, in degrees
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_cell%copy(cell[, status])

Initialize this unit cell with a copy of cell.

Parameters:cell [chfl_cell] :: cell to copy
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_cell%from_frame(frame[, status])

Initialize this topology with a copy of the chfl_cell of a frame.

Parameters:frame [chfl_frame] :: the frame
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_cell%volume(volume[, status])

Get the volume of the unit cell in volume.

Parameters:volume [real] :: volume of the unit cell
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_cell%lengths(lengths[, status])

Get the unit cell lengths in lengths.

Parameters:lengths (3) [real] :: cell lengths, in angstroms
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_cell%set_lengths(lengths[, status])

Set the unit cell lengths to lengths.

Parameters:lengths (3) [real] :: new cell lengths, in angstroms
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_cell%angles(angles[, status])

Get the unit cell angles in angles.

Parameters:angles (3) [real] :: cell angles, in degrees
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_cell%set_angles(alpha, beta, gamma[, status])

Set the cell angles to angles. Trying to set cell angles on a cell which is not triclinic (does not have the CHFL_CELL_TRICLINIC shape) is an error.

Parameters:angles (3) [real] :: new cell angles, in degrees
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_cell%matrix(matrix[, status])

Get the unit cell matricial representation in matrix.

The unit cell representation is obtained by aligning the a vector along the x axis and putting the b vector in the xy plane. This make the matrix an upper triangular matrix:

| a_x b_x c_x |
|  0  b_y c_y |
|  0   0  c_z |
Parameters:matrix (3, 3) [real] :: unit cell matrix
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_cell%shape(shape[, status])

Get the unit cell shape in shape.

Parameters:type [integer,kind=chfl_cell_shape_t] :: the shape of the cell
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

The cell shapes are integers which kind is the chfl_cell_shape_t parameter:

integer(chfl_cell_shape_t) :: CHFL_CELL_ORTHORHOMBIC

The three angles are 90°

integer(chfl_cell_shape_t) :: CHFL_CELL_TRICLINIC

The three angles may not be 90°

integer(chfl_cell_shape_t) :: CHFL_CELL_INFINITE

Cell type when there is no periodic boundary conditions

subroutine chfl_cell%set_shape(shape[, status])

Set the unit cell shape to shape

Parameters:type [integer,kind=chfl_cell_shape_t] :: the new type of the cell
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_cell%free([status])

Destroy an unit cell, and free the associated memory

Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

chfl_topology type

type chfl_topology

A chfl_topology contains the definition of all the atoms in the system, and the liaisons between the atoms (bonds, angles, dihedrals, …). It will also contain all the residues information if it is available.

The initialization routine for chfl_topology are chfl_topology%init(), chfl_topology%from_frame() and chfl_topology%copy().

Type fields:
subroutine chfl_topology%init([status])

Initialize this topology with a new empty topology.

Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_topology%from_frame(frame[, status])

Initialize this topology with a copy of the topology of frame.

Parameters:frame [chfl_frame] :: the frame
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_topology%copy(topology[, status])

Initialize this topology with a copy of topology.

Parameters:topology [chfl_topology] :: topology to copy
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_topology%atoms_count(natoms[, status])

Get the number of atoms in the topology in natoms.

Parameters:natoms [integer] :: number of atoms in the topology
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_topology%resize(natoms[, status])

Resize the topology to hold natoms atoms. If the new number of atoms is bigger than the current number, new atoms will be created with an empty name and type. If it is lower than the current number of atoms, the last atoms will be removed, together with the associated bonds, angles and dihedrals.

Parameters:natoms [integer] :: new size of the topology
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_topology%add_atom(atom[, status])

Add a copy of atom at the end of the topology.

Parameters:atom [chfl_atom] :: atom to be added
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_topology%remove(i[, status])

Remove the atom at index i from the topology.

This shifts all the atoms indexes after i by 1 (n becomes n-1).

Parameters:i [integer] :: index of the atom to remove
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_topology%isbond(i, j, result[, status])

Check if the atoms at indexes i and j are bonded together, and store the result in result.

Parameters:
  • i [integer] :: atomic index of the first atom
  • j [integer] :: atomic index of the second atom
  • result [logical,kind=1] :: .true. if the atoms are bonded, .false. otherwise
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_topology%isangle(i, j, k, result[, status])

Check if the atoms at indexes i, j and k form an angle, and store the result in result.

Parameters:
  • i [integer] :: atomic index of the first atom
  • j [integer] :: atomic index of the second atom
  • k [integer] :: atomic index of the third atom
  • result [logical,kind=1] :: .true. if the atoms form an angle, .false. otherwise
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_topology%isdihedral(i, j, k, m, result[, status])

Check if the atoms at indexes i, j, k and m form a dihedral angle, and store the result in result.

Parameters:
  • i [integer] :: atomic index of the first atom
  • j [integer] :: atomic index of the second atom
  • k [integer] :: atomic index of the third atom
  • m [integer] :: atomic index of the fourth atom
  • result [logical,kind=1] :: .true. if the atoms form a dihedral angle, .false. otherwise
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_topology%bonds_count(nbonds[, status])

Get the number of bonds in the topology in nbonds.

Parameters:nbonds [integer] :: number of bonds
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_topology%angles_count(nangles[, status])

Get the number of angles in the topology in nangles.

Parameters:nangles [integer] :: number of angles
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_topology%dihedrals_count(ndihedrals[, status])

Get the number of dihedral angles in the topology in ndihedrals.

Parameters:ndihedrals [integer] :: number of dihedral angles
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_topology%bonds(data, nbonds[, status])

Get the list of bonds in the topology in the pre-allocated array data of size 2 x nbonds.

data size must be passed in the nbonds parameter, and be equal to the result of chfl_topology%bonds_count().

Parameters:
  • data (2, nbonds) [integer] :: 2 x nbonds array to be filled with the bonds in the system
  • nbonds [integer] :: size of the array. This should be equal to the value given by chfl_topology%bonds_count().
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_topology%angles(data, nangles[, status])

Get the list of angles in the topology in the pre-allocated array data of size 3 x nangles.

data size must be passed in the nangles parameter, and be equal to the result of chfl_topology%angles_count().

Parameters:
  • data (3, nangles) [integer] :: 3 x nangles array to be filled with the angles in the system
  • nangles [integer] :: size of the array. This should be equal to the value given by chfl_topology%angles_count().
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_topology%dihedrals(data, ndihedrals[, status])

Get the list of dihedral angles in the topology in the pre-allocated array data of size 4 x ndihedrals.

data size must be passed in the ndihedrals parameter, and be equal to the result of chfl_topology%dihedrals_count().

Parameters:
  • data (4, ndihedrals) [integer] :: 4 x ndihedrals array to be filled with the dihedral angles in the system
  • ndihedrals [integer] :: size of the array. This should be equal to the value given by chfl_topology%dihedrals_count().
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_topology%add_bond(i, j[, status])

Add a bond between the atoms at indexes i and j in the topology

Parameters:
  • i [integer] :: atomic index of the first atom of the bond
  • j [integer] :: atomic index of the second atom of the bond
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_topology%remove_bond(i, j[, status])

Remove any existing bond between the atoms at indexes i and j in the topology.

This function does nothing if there is no bond between i and j.

Parameters:
  • i [integer] :: The atomic index of the first atom
  • j [integer] :: The atomic index of the second atom
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_topology%residues_count(natoms[, status])

Get the number of residues in the topology in nresidues.

Parameters:natoms [integer] :: number of residues
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_topology%add_residue(residue[, status])

Add a copy of residue to this topology.

The residue id must not already be in the topology, and the residue must contain only atoms that are not already in another residue.

Parameters:residue [chfl_residue] :: residue to add in the topology
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_topology%residues_linked(first, second, are_linked[, status])

Check if the two residues first and second from the topology are linked together, i.e. if there is a bond between one atom in the first residue and one atom in the second one, and store the result in result.

Parameters:
  • first [chfl_residue] :: first residue
  • second [chfl_residue] :: second residue
  • are_linked [logical,kind=1] :: .true. if the residues are linked, .false. otherwise
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_topology%free([status])

Destroy a topology, and free the associated memory

Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

chfl_residue type

type chfl_residue

A chfl_residue is a group of atoms belonging to the same logical unit. They can be small molecules, amino-acids in a protein, monomers in polymers, etc.

The initialization routine for chfl_residue are chfl_residue%init(), chfl_residue%from_topology(), chfl_residue%for_atom() and chfl_residue%copy().

Type fields:
subroutine chfl_residue%init(name[, id, status])

Initialize the residue with a new residue with the given name and optional residue identifier id.

Parameters:

name [character,len=*] :: residue name

Options:
  • id [integer] :: residue id
  • status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_residue%copy(residue[, status])

Initialize this residue with a copy of residue.

Parameters:residue [chfl_residue] :: residue to copy
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_residue%from_topology(topology, i[, status])

Initialize this residue with a copy of the residue at index i from a topology. The residue index in the topology is not always the same as the residue id.

Parameters:
  • topology [chfl_topology] :: topology
  • i [integer] :: index of the residue in the topology
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_residue%for_atom(topology, i[, status])

Get a copy of the residue containing the atom at index i in the topology.

Parameters:
  • topology [chfl_topology] :: topology
  • i [integer] :: index of the atom in the topology
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_residue%name(name, buffsize[, status])

Get the name of the residue in the string buffer name.

The buffer size must be passed in buffsize. This function will truncate the residue name to fit in the buffer.

Parameters:
  • name [character,len=buffsize] :: string buffer to be filled with the residue name
  • buffsize :: length of the string buffer
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_residue%id(id[, status])

Get the identifier of the residue in the initial topology file in id

Parameters:id [integer] :: identifier of the residue
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_residue%atoms_count(size[, status])

Get the number of atoms in the residue in size.

Parameters:size [integer] :: number of atoms in the residue
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_residue%add_atom(i[, status])

Add the atom at index i in the residue.

Parameters:i [integer] :: index of the atom to add
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_residue%contains(i, result[, status])

Check if the atom at index i is in the residue, and store the result in result.

Parameters:
  • i [integer] :: index of the atom
  • result [logical,kind=1] :: .true. if the atom is in the residue, .false. otherwise
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_residue%free([status])

Destroy a residue, and free the associated memory

Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

chfl_atom type

type chfl_atom

A chfl_atom is a particle in the current chfl_frame. It stores the following atomic properties:

  • atom name;
  • atom type;
  • atom mass;
  • atom charge.

The atom name is usually an unique identifier (H1, C_a) while the atom type will be shared between all particles of the same type: H, Ow, CH3.

The initialization routine for chfl_atom are chfl_atom%init(), chfl_atom%from_frame() and chfl_atom%from_topology().

Type fields:
subroutine chfl_atom%init(name[, status])

Initialize this atom with the given name, and set the atom type to name.

Parameters:name [character,len=*] :: atom name
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_atom%copy(atom[, status])

Initialize this atom with a copy of atom.

Parameters:atom [chfl_atom] :: atom to copy
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_atom%from_frame(frame, i[, status])

Initialize this atom with a copy the atom at index i from a frame.

Parameters:
  • frame [chfl_frame] :: frame
  • i [integer] :: atom index in the frame
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_atom%from_topology(topology, i[, status])

Initialize this atom with a copy the atom at index i from a topology.

Parameters:
  • topology [chfl_topology] :: topology
  • idx [integer] :: atom index in the topology
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_atom%mass(mass[, status])

Get the mass of tah atom in mass. The mass is in atomic mass units.

Parameters:mass [real] :: atom mass
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_atom%set_mass(mass[, status])

Set the mass of the atom to mass. The mass should be in atomic mass units.

Parameters:mass [real] :: new atom mass
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_atom%charge(charge[, status])

Get the charge of the atom in charge. The charge is in number of the electron charge e.

Parameters:charge [real] :: The atom charge
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_atom%set_charge(charge[, status])

Get the charge of the atom to charge. The charge should be in number of the electron charge e.

Parameters:charge [real] :: new atom charge
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_atom%name(name, buffsize[, status])

Get the name of an atom in the string buffer name.

The buffer size must be passed in buffsize. This function will truncate the name to fit in the buffer.

Parameters:
  • name [character,len=buffsize] :: string buffer to be filled with the atom name
  • buffsize :: length of the string buffer
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_atom%set_name(name[, status])

Set the name of an atom to name.

Parameters:name [character,len=*] :: new atom name
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_atom%full_name(name, buffsize[, status])

Get the full name of an atom from its type in the string buffer name.

The buffer size must be passed in buffsize. This function will truncate the name to fit in the buffer.

Parameters:
  • name [character,len=buffsize] :: string buffer to be filled with the atom full name
  • buffsize :: length of the string buffer
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_atom%type(type, buffsize[, status])

Get the type of an atom in the string buffer type.

The buffer size must be passed in buffsize. This function will truncate the type to fit in the buffer.

Parameters:
  • name [character,len=buffsize] :: string buffer to be filled with the atom type
  • buffsize :: length of the string buffer
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_atom%set_type(type[, status])

Set the type of an atom to type.

Parameters:name [character,len=*] :: new atom type
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_atom%vdw_radius(radius[, status])

Get the Van der Waals radius of an atom from the atom type in radius.

If the radius in unknown, this function set radius to -1.

Parameters:radius [real] :: Van der Waals radius
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_atom%covalent_radius(radius[, status])

Get the covalent radius of an atom from the atom type in radius.

If the radius in unknown, this function set radius to -1.

Parameters:radius [real] :: covalent radius
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_atom%atomic_number(number[, status])

Get the atomic number of an atom from the atom type in number.

If the atomic number in unknown, this function set number to -1.

Parameters:number [integer] :: atomic number
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_atom%free([status])

Destroy an atom, and free the associated memory

Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

chfl_selection type

type chfl_selection

chfl_selection allow to select atoms in a chfl_frame, from a selection language. The selection language is built by combining basic operations. Each basic operation follows the <selector>[(<variable>)] <operator> <value> structure, where <operator> is a comparison operator in == != < <= > >=.

The initialization routines for chfl_selection are chfl_selection%init() and chfl_selection%copy().

Type fields:
subroutine chfl_selection%init(selection[, status])

Initialize the selection with a new selection from the given selection string.

See the selection documentation for the selection language specification.

Parameters:selection [character,len=*] :: The selection string
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_selection%copy(selection[, status])

Initialize the selection with a copy of selection.

The copy does not contains any state, and chfl_selection%evaluate() must be called again before using chfl_selection%matches().

Parameters:selection [chfl_selection] :: selection to copy
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_selection%size(size[, status])

Get the size of the selection in size.

The size of a selection is the number of atoms we are selecting together. This value is 1 for the ‘atom’ context, 2 for the ‘pair’ and ‘bond’ context, 3 for the ‘three’ and ‘angles’ contextes and 4 for the ‘four’ and ‘dihedral’ contextes.

Parameters:size [integer] :: selection size
Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
subroutine chfl_selection%string(string, buffsize[, status])

Get the selection string used to create this selection in the string buffer.

The buffer size must be passed in buffsize. This function will truncate the selection string to fit in the buffer.

Parameters:
  • size [character,len=buffsize] :: string buffer to be filled with the initial selection string
  • buffsize [integer] :: size of the string buffer
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_selection%evaluate(frame, nmatches[, status])

Evaluate the selection for a given frame, and store the number of matches in nmatches. Use chfl_selection%matches() to get the matches.

Parameters:
  • frame [chfl_frame] :: frame to evaluate
  • n_matches [integer] :: number of matches for this selection
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_selection%matches(matches, n[, status])

Get the matches for the selection after a call to chfl_selection%evalutate(), in the pre-allocated matches array. The size of the matches array must be passed in n.

Parameters:
  • matches (nmatchs) [chfl_match,allocatable] :: Pre-allocated array of the size given by chfl_selection%evaluate.
  • n [integer] :: size of the matches array
Options:

status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.

subroutine chfl_selection%free([status])

Destroy a selection, and free the associated memory

Options:status [integer,optional, kind=chfl_status] :: status code of the operation. If it is not equal to CHFL_SUCCESS, you can learn more about the error by using chfl_last_error.
type chfl_match

This type contains the matched atoms for a given selection in the atoms array. Values in the atoms array are valid up to the size of this match. If the match size is 2, then atom(1) and atom(2) are valid, and atom(3) and atom(4) contains invalid indexes.

Type fields:
  • % size [integer] :: The size of this match.
  • % atoms (4) [integer] :: The index of the matched atoms.