The chemfiles module is built around the 5 main types of chemfiles: chfl_trajectory,
chfl_frame, chfl_cell, chfl_topology, and chfl_atom. 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 function. Fortran arrays returned by function still have indexes starting at 1.
program indexing
use iso_fortran_env, only: real32, int64
use chemfiles
implicit none
type(chfl_frame) :: frame
type(chfl_atom) :: atom
real(real32), pointer :: positions(:, :)
integer(int64) :: natoms
! Read the frame here
! 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
This may change in future release to make all atomic number starting at 1, which is more familiar to Fortran developers and would be less confusing.
All the functions and types have the chfl_ prefix. Except for the chfl_strerror
and chfl_last_error functions, all the functions take a status argument,
which will indicate the status of the operation. It should be 0 if everything
was OK, and can be any other number in case of 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.
implicit none
type(chfl_cell) :: cell
type(chfl_frame) :: frame
call cell%init(20, 20, 20, 90, 90, 90)
call frame%init(3)
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 segmentations faults.
string chfl_version([status])Get the version of the chemfiles library as a string.
| Options: | status [integer,optional] :: The status code |
|---|
string chfl_strerror(status)Get the error message corresponding to an error code.
| Parameters: | status [integer] :: The status code |
|---|---|
| Return: | strerror [string] :: The error message corresponding to the status code |
string chfl_last_error()Get the last error message.
| Return: | strerror [string] :: The error message corresponding to the status code |
|---|
chfl_loglevel(level[, status])¶Get the current maximal logging level
| Parameters: | level [integer,kind=CHFL_LOG_LEVEL] :: A variable that will contain the logging level |
|---|---|
| Options: | status [integer,optional] :: The status code |
The logging level are integers which kind is the parameter CHFL_LOG_LEVEL:
integer(CHFL_LOG_LEVEL) :: CHFL_LOG_ERROROnly log errors
integer(CHFL_LOG_LEVEL) :: CHFL_LOG_WARNINGLog warnings and erors. This is the default.
integer(CHFL_LOG_LEVEL) :: CHFL_LOG_INFOLog infos, warnings and errors
integer(CHFL_LOG_LEVEL) :: CHFL_LOG_DEBUGLog everything
chfl_set_loglevel(level[, status])¶Set the maximal logging level to level
| Parameters: | level [integer,kind=CHFL_LOG_LEVEL] :: The new logging level |
|---|---|
| Options: | status [integer,optional] :: The status code |
chfl_logfile(file[, status])¶Redirect the logs to file, overwriting the file if it exists.
| Parameters: | file [string] :: The path to the log file |
|---|---|
| Options: | status [integer,optional] :: The status code |
chfl_log_stderr([status])¶Redirect the logs to the standard error output. This is enabled by default.
| Options: | status [integer,optional] :: The status code |
|---|
chfl_log_stdout([status])¶Redirect the logs to the standard output.
| Options: | status [integer,optional] :: The status code |
|---|
chfl_log_silent([status])¶Remove all logging output.
| Options: | status [integer,optional] :: The status code |
|---|
chfl_log_callback(callback[, status])¶Redirect all logging to user-provided logging. The callback subroutine will
be called at each logging operation with the level of the message, and the the
message itself.
| Parameters: | procedure (chfl_logging_callback) :: The callback procedure |
|---|---|
| Options: | status [integer,optional] :: The status code |
chfl_logging_callback(level, message)¶This is the interface for callback functions in the logging system. At every log event, this function will be called with the level and the message of the log event.
| Parameters: |
|
|---|
chfl_trajectory type¶chfl_trajectory¶Wrapping around a C pointer of type CHFL_TRAJECTORY*. The following
subroutine are available:
| Type fields: |
|
|---|
The initialization routine are open and with_format, and the memory
liberation routine is close.
open(filename, mode[, status])¶Open a trajectory file.
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
with_format(filename, mode[, status])¶Open a trajectory file using a given format to read the file.
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
read(frame[, status])¶Read the next step of the trajectory into a frame
| Parameters: | frame [chfl_frame] :: A frame to fill with the data |
|---|---|
| Options: | status [integer,optional] :: The status code |
read_step(step, frame[, status])¶Read a specific step of the trajectory in a frame
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
write(frame[, status])¶Write a frame to the trajectory.
| Parameters: | frame [chfl_frame] :: the frame which will be writen to the file |
|---|---|
| Options: | status [integer,optional] :: The status code |
set_topology(topology[, status])¶Set the topology associated with a trajectory. This topology will be used when reading and writing the files, replacing any topology in the frames or files.
| Parameters: | topology [chfl_topology] :: The new topology to use |
|---|---|
| Options: | status [integer,optional] :: The status code |
set_topology_file(filename[, status])¶Set the topology associated with a trajectory by reading the first
frame of filename; and extracting the topology of this frame.
| Parameters: | filename [string] :: The file to read in order to get the new topology |
|---|---|
| Options: | status [integer,optional] :: The status code |
cell(cell[, status])¶Set the unit cell associated with a trajectory. This cell will be used when reading and writing the files, replacing any unit cell in the frames or files.
| Parameters: | cell [chfl_cell] :: The new cell to use |
|---|---|
| Options: | status [integer,optional] :: The status code |
nsteps(nsteps[, status])¶Get the number of steps (the number of frames) in a trajectory.
| Parameters: | nsteps [integer] :: This will contain the number of steps |
|---|---|
| Options: | status [integer,optional] :: The status code |
sync([status])¶Flush any buffered content to the hard drive.
| Options: | status [integer,optional] :: The status code |
|---|
close([status])¶Close a trajectory file, and free the associated memory
| Options: | status [integer,optional] :: The status code |
|---|
chfl_frame type¶chfl_frame¶Wrapping around a C pointer of type CHFL_FRAME*. The following
subroutine are available:
| Type fields: |
|
|---|
init(natoms[, status])¶Create an empty frame with initial capacity of natoms. It will be
resized by the library as needed.
| Parameters: | natoms [integer] :: the size of the wanted frame |
|---|---|
| Options: | status [integer,optional] :: The status code |
atoms_count(natoms[, status])¶Get the current number of atoms in the frame
| Parameters: | natoms [integer] :: the number of atoms in the frame |
|---|---|
| Options: | status [integer,optional] :: The status code |
resize(natoms[, status])¶Resize the positions and the velocities in frame, to make 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 of abscence of velocities.
| Parameters: | natoms [integer] :: the new number of atoms in the frame |
|---|---|
| Options: | status [integer,optional] :: The status code |
positions(data, size[, status])¶Get a pointer to the positions array from a frame. The positions are stored as a 3
x N array, this function set a pointer to point to the first element of this array,
and give the value of N in the size argument. If the frame is resized (by writing
to it, or calling chfl_frame%resize), the pointer is invalidated.
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
velocities(data, size[, status])¶Get a pointer to the velocities array from a frame. The velocities are stored as a 3
x N array, this function set a pointer to point to the first element of this array,
and give the value of N in the size argument. If the frame is resized (by writing
to it, or calling chfl_frame%resize), the pointer is invalidated.
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
add_velocities([status])¶Add velocity storage to this frame. The storage is initialized with the result of
chfl_frame%atoms_count as number of atoms. If the frame already have velocities,
this does nothing.
| Options: | status [integer,optional] :: The status code |
|---|
has_velocities(has_vel[, status])¶Check if a frame has velocity information.
| Parameters: | has_vel [logical] :: .true. if the frame has velocities, .false. otherwise. |
|---|---|
| Options: | status [integer,optional] :: The status code |
set_cell(cell[, status])¶Set the UnitCell of a Frame.
| Parameters: | cell [chfl_cell] :: The new unit cell |
|---|---|
| Options: | status [integer,optional] :: The status code |
set_topology(topology[, status])Set the Topology of a Frame.
| Parameters: | topology [chfl_topology] :: The new topology |
|---|---|
| Options: | status [integer,optional] :: The status code |
step(step[, status])¶Get the Frame step, i.e. the frame number in the trajectory
| Parameters: | step [integer] :: This will contains the step number |
|---|---|
| Options: | status [integer,optional] :: The status code |
set_step(step[, status])¶Set the Frame step.
| Parameters: | step [integer] :: The new frame step |
|---|---|
| Options: | status [integer,optional] :: The status code |
guess_topology(bonds[, status])¶Try to guess the bonds, angles and dihedrals in the system. If bonds
is .true., guess everything; else only guess the angles and dihedrals from
the bond list.
| Parameters: | bonds [logical] :: Should we recompute the bonds from the positions or not ? |
|---|---|
| Options: | status [integer,optional] :: The status code |
selection(selection, matched, natoms)¶Select atoms in a frame, from a specific selection string.
This function select atoms in a frame matching a selection string. For example,
"name H and x > 4" will select all the atoms with name "H" and x
coordinate less than 4. See the C++ documentation for the full selection language.
Results of this function are used to fill the matched pre-allocated array
containing natoms logical, where natoms is the number of atoms in the frame.
The array will contain .true. at position i if the atom at position i
matches the selection string, and false otherwise.
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
free([status])¶Destroy a frame, and free the associated memory
| Options: | status [integer,optional] :: The status code |
|---|
chfl_cell type¶chfl_cell¶Wrapping around a C pointer of type CHFL_CELL*. The following
subroutine are available:
| Type fields: |
|
|---|
The initialization routine are init and from_frame.
init(a, b, c, alpha, beta, gamma[, status])Create an chfl_cell from the three lenghts and the three angles.
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
from_frame_init_(frame[, status])¶Get a copy of the chfl_cell of a frame.
| Parameters: | frame [chfl_frame] :: the frame |
|---|---|
| Options: | status [integer,optional] :: The status code |
lengths(a, b, c[, status])¶Get the cell lenghts.
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
set_lengths(a, b, c[, status])¶Set the unit cell lenghts.
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
angles(alpha, beta, gamma[, status])¶Get the cell angles, in degrees.
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
set_angles(alpha, beta, gamma[, status])¶Set the cell angles, in degrees
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
matrix(matrix[, status])¶Get the unit cell matricial representation, i.e. the representation of the three base vectors arranged as:
| a_x b_x c_x |
| 0 b_y c_y |
| 0 0 c_z |
| Parameters: | matrix [real,dimension(3, 3)] :: the matrix to fill. |
|---|---|
| Options: | status [integer,optional] :: The status code |
type(type[, status])¶Get the cell type
| Parameters: | type [integer,kind=CHFL_CELL_TYPES] :: the type of the cell |
|---|---|
| Options: | status [integer,optional] :: The status code |
The cell types are integers which kind is the parameter CHFL_CELL_TYPES:
integer(CHFL_CELL_TYPES) :: CHFL_CELL_ORTHOROMBICThe three angles are 90°
integer(CHFL_CELL_TYPES) :: CHFL_CELL_TRICLINICThe three angles may not be 90°
integer(CHFL_CELL_TYPES) :: CHFL_CELL_INFINITECell type when there is no periodic boundary conditions
set_type(type[, status])¶Set the cell type
| Parameters: | type [integer,kind=CHFL_CELL_TYPES] :: the new type of the cell |
|---|---|
| Options: | status [integer,optional] :: The status code |
free([status])Destroy an unit cell, and free the associated memory
| Options: | status [integer,optional] :: The status code |
|---|
chfl_topology type¶chfl_topology¶Wrapping around a C pointer of type CHFL_TOPOLOGY*. The following
subroutine are available:
| Type fields: |
|
|---|
The initialization routine are init and from_frame.
init([status])Create a new empty topology
| Options: | status [integer,optional] :: The status code |
|---|
from_frame(frame[, status])¶Extract the topology from a frame.
| Parameters: | frame [chfl_frame] :: The frame |
|---|---|
| Options: | status [integer,optional] :: The status code |
atoms_count(natoms[, status])Get the current number of atoms in the topology.
| Parameters: | natoms [integer] :: Will contain the number of atoms in the frame |
|---|---|
| Options: | status [integer,optional] :: The status code |
append(atom[, status])¶Add an atom at the end of a topology.
| Parameters: | atom [chfl_atom] :: The atom to be added |
|---|---|
| Options: | status [integer,optional] :: The status code |
remove(i[, status])¶Remove an atom from a topology by index.
| Parameters: | i [integer] :: The atomic index |
|---|---|
| Options: | status [integer,optional] :: The status code |
isbond(i, j, result[, status])¶Tell if the atoms i and j are bonded together
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
isangle(i, j, k, result[, status])¶Tell if the atoms i, j and k constitues an angle
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
isdihedral(i, j, k, m, result[, status])¶Tell if the atoms i, j, k and m constitues a dihedral angle
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
bonds_count(nbonds[, status])¶Get the number of bonds in the system
| Parameters: | nbonds [integer] :: After the call, contains the number of bond |
|---|---|
| Options: | status [integer,optional] :: The status code |
angles_count(nangles[, status])¶Get the number of angles in the system
| Parameters: | nangles [integer] :: After the call, contains the number of angles |
|---|---|
| Options: | status [integer,optional] :: The status code |
dihedrals_count(ndihedrals[, status])¶Get the number of dihedral angles in the system
| Parameters: | ndihedrals [integer] :: After the call, contains the number of dihedral angles |
|---|---|
| Options: | status [integer,optional] :: The status code |
bonds(data, nbonds[, status])¶Get the bonds in the system
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
angles(data, nangles[, status])Get the angles in the system
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
dihedrals(data, ndihedrals[, status])¶Get the dihedral angles in the system
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
add_bond(i, j[, status])¶Add a bond between the atoms i and j in the system
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
remove_bond(i, j[, status])¶Remove any existing bond between the atoms i and j in the system
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
free([status])Destroy a topology, and free the associated memory
| Options: | status [integer,optional] :: The status code |
|---|
chfl_atom type¶chfl_atom¶Wrapping around a C pointer of type CHFL_ATOM*. The following
subroutine are available:
| Type fields: |
|
|---|
The initialization routine are init, from_frame and from_topology.
init(name[, status])Create an atom from an atomic name
| Parameters: | name [string] :: The new atom name |
|---|---|
| Options: | status [integer,optional] :: The status code |
from_frame(frame, idx[, status])Get a specific atom from a frame
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
from_topology(topology, idx[, status])¶Get a specific atom from a topology
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
mass(mass[, status])¶Get the mass of an atom, in atomic mass units
| Parameters: | mass [real] :: The atom mass |
|---|---|
| Options: | status [integer,optional] :: The status code |
set_mass(mass[, status])¶Set the mass of an atom, in atomic mass units
| Parameters: | mass [real] :: The new atom mass |
|---|---|
| Options: | status [integer,optional] :: The status code |
charge(charge[, status])¶Get the charge of an atom, in number of the electron charge e
| Parameters: | charge [real] :: The atom charge |
|---|---|
| Options: | status [integer,optional] :: The status code |
set_charge(charge[, status])¶Set the charge of an atom, in number of the electron charge e
| Parameters: | charge [real] :: The new atom charge |
|---|---|
| Options: | status [integer,optional] :: The status code |
name(name, buffsize[, status])¶Get the name of an atom
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
set_name(name[, status])¶Set the name of an atom
| Parameters: | name [string] :: A string containing the new name |
|---|---|
| Options: | status [integer,optional] :: The status code |
full_name(name, buffsize[, status])¶Try to get the full name of an atom from the short name
| Parameters: |
|
|---|---|
| Options: | status [integer,optional] :: The status code |
vdw_radius(radius[, status])¶Try to get the Van der Waals radius of an atom from the short name
| Parameters: | radius [real] :: The Van der Waals radius of the atom or -1 if no value could be found. |
|---|---|
| Options: | status [integer,optional] :: The status code |
covalent_radius(radius[, status])¶Try to get the covalent radius of an atom from the short name
| Parameters: | radius [real] :: The covalent radius of the atom or -1 if no value could be found. |
|---|---|
| Options: | status [integer,optional] :: The status code |
atomic_number(number[, status])¶Try to get the atomic number of an atom from the short name
| Parameters: | number [integer] :: The atomic number, or -1 if no value could be found. |
|---|---|
| Options: | status [integer,optional] :: The status code |
type(type[, status])Get the atom type
| Parameters: | type [integer,kind=CHFL_ATOM_TYPES] :: the type of the atom |
|---|---|
| Options: | status [integer,optional] :: The status code |
The atom types are integers which kind is the parameter CHFL_ATOM_TYPES:
integer(CHFL_ATOM_TYPES) :: CHFL_ATOM_ELEMENTElement from the periodic table of elements.
integer(CHFL_ATOM_TYPES) :: CHFL_ATOM_COARSE_GRAINEDCoarse-grained atom are composed of more than one element: CH3 groups, amino-acids are coarse-grained atoms.
integer(CHFL_ATOM_TYPES) :: CHFL_ATOM_DUMMYDummy site, with no physical reality.
integer(CHFL_ATOM_TYPES) :: CHFL_ATOM_UNDEFINEDUndefined atom type.
set_type(type[, status])Set the atom type
| Parameters: | type [integer,kind=CHFL_ATOM_TYPES] :: the new type of the atom |
|---|---|
| Options: | status [integer,optional] :: The status code |
free([status])Destroy an atom, and free the associated memory
| Options: | status [integer,optional] :: The status code |
|---|