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.- Type fields:
% init [subroutine] ::
chfl_frame%init()
% copy [subroutine] ::
chfl_frame%copy()
% atoms_count [function] ::
chfl_frame%atoms_count()
% add_atom [subroutine] ::
chfl_frame%add_atom()
% atom [function] ::
chfl_frame%atom()
% remove [subroutine] ::
chfl_frame%remove()
% resize [subroutine] ::
chfl_frame%resize()
% add_bond [subroutine] ::
chfl_frame%add_bond()
% remove_bond [subroutine] ::
chfl_frame%remove_bond()
% clear_bonds [subroutine] ::
chfl_frame%clear_bonds()
% add_residue [subroutine] ::
chfl_frame%add_residue()
% distance [function] ::
chfl_frame%distance()
% angle [function] ::
chfl_frame%angle()
% dihedral [function] ::
chfl_frame%dihedral()
% out_of_plane [function] ::
chfl_frame%out_of_plane()
% positions [function] ::
chfl_frame%positions()
% velocities [function] ::
chfl_frame%velocities()
% add_velocities [subroutine] ::
chfl_frame%add_velocities()
% has_velocities [subroutine] ::
chfl_frame%has_velocities()
% cell [subroutine] ::
chfl_frame%cell()
% set_cell [subroutine] ::
chfl_frame%set_cell()
% topology [function] ::
chfl_frame%topology()
% set_topology [subroutine] ::
chfl_frame%set_topology()
% guess_bonds [subroutine] ::
chfl_frame%guess_bonds()
% step [function] ::
chfl_frame%step()
% set_step [subroutine] ::
chfl_frame%set_step()
% set [subroutine] ::
chfl_frame%set()
% get [function] ::
chfl_frame%get()
% properties_count [function] ::
chfl_frame%properties_count()
% list_properties [subroutine] ::
chfl_frame%list_properties()
% free [subroutine] ::
chfl_frame%free()
- subroutine chfl_frame%init([status])¶
Initialize this frame as an empty frame. This subroutine allocate memory which must be released with
chfl_frame%free()
.- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- subroutine chfl_frame%copy(frame[, status])¶
Initialize this frame with a copy of
frame
. This subroutine allocate memory which must be released withchfl_frame%free()
.- Parameters:
frame [type(chfl_frame)] :: frame to copy
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- function chfl_frame%atoms_count([status])¶
Get the current number of atoms in the frame in
natoms
.- Parameters:
natoms [integer] :: number of atoms in the frame
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- subroutine chfl_frame%add_atom(atom, position[, velocity, status])¶
Add a
chfl_atom
and the correspondingposition
andvelocity
data to this frame.velocity
can be absent if no velocity is associated with this frame.- Parameters:
atom [type(chfl_atom)] :: atom to add to the frame
position (3) [real] :: atom position
- Options:
velocity (3) [real,optional] :: atom velocity
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- function chfl_frame%atom(index[, status])¶
Get access to the atom at the given
index
in this frame.Any modification to the atom will be reflected in the frame. The frame will be kept alive, even if
chfl_frame%free()
is called, untilchfl_atom%free()
is also called on the atom returned by this function.The atom returned by this function is a pointer that points directly inside the frame, and will be invalidated if any of the following function is called on the frame:
Calling any function on an invalidated pointer is undefined behavior. Even if the pointer if invalidated, it stills needs to be released with
chfl_atom%free()
.- Return:
type (chfl_atom)
- Parameters:
index [integer] :: Index of the atom in the frame
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the 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 usingchfl_frame%positions()
orchfl_frame%velocities()
.- Parameters:
index [integer] :: index of the atom to remove
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the 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(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- subroutine chfl_frame%add_bond(i, j[, bond_order, status])¶
Add a bond between the atoms at indexes
i
andj
in the frame’s topology, and optionaly set thebond_order
. By default, a bond order ofCHFL_BOND_UNKNOWN
is used.Possible bond orders are represented by an integer of kind
chfl_bond_order
.- Parameters:
i [integer] :: atomic index of the first atom of the bond
j [integer] :: atomic index of the second atom of the bond
- Options:
bond_order [integer(chfl_bond_order)] :: order of the bond
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- subroutine chfl_frame%remove_bond(i, j[, status])¶
Remove any existing bond between the atoms at indexes
i
andj
in the frame’s topology.This function does nothing if there is no bond between
i
andj
.- Parameters:
i [integer] :: atomic index of the first atom
j [integer] :: atomic index of the second atom
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- subroutine chfl_frame%clear_bonds([status])¶
Remove all bonds in this frame.
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- subroutine chfl_frame%add_residue(residue[, status])¶
Add a copy of
residue
to this frame’s 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 [type(chfl_residue)] :: residue to add in the topology
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- function chfl_frame%distance(i, j[, status])¶
Get the distance between the atoms at indexes
i
andj
in this frame, accounting for periodic boundary conditions and expressed in angstroms.- Return:
real
- Parameters:
i [integer] :: atomic index of the first atom of the pair
j [integer] :: atomic index of the second atom of the pair
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- function chfl_frame%angle(i, j, k[, status])¶
Get the angle formed by the atoms at indexes
i
,j
andk
in this frame, accounting for periodic boundary conditions, and expressed in radians.- Return:
real
- Parameters:
i [integer] :: atomic index of the first atom of the angle
j [integer] :: atomic index of the second atom of the angle
k [integer] :: atomic index of the third atom of the angle
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- function chfl_frame%dihedral(i, j, k, m[, status])¶
Get the dihedral angle formed by the atoms at indexes
i
,j
,k
andm
in this frame, accounting for periodic boundary conditions, and expressed in radians.- Return:
real
- Parameters:
i [integer] :: atomic index of the first atom of the angle
j [integer] :: atomic index of the second atom of the angle
k [integer] :: atomic index of the third atom of the angle
m [integer] :: atomic index of the fourth atom of the angle
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- function chfl_frame%out_of_plane(i, j, k, m[, status])¶
Get the out of plane distance formed by the atoms at indexes
i
,j
,k
andm
in this frame, accounting for periodic boundary conditions. The result is expressed in angstroms.This is the distance between the atom j and the ikm plane. The atom j is the center of the improper dihedral angle formed by i, j, k and m.
- Return:
real
- Parameters:
i [integer] :: atomic index of the first atom of the angle
j [integer] :: atomic index of the second atom of the angle
k [integer] :: atomic index of the third atom of the angle
m [integer] :: atomic index of the fourth atom of the angle
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- function chfl_frame%positions(data, size[, status])¶
Get a pointer to the positions array from the frame.
This function gives access to chemfiles internal data structure, and do not perform any copy, both when reading and writing the positions.
- The pointer is invalidated if any of the following function is called:
When the memory of the frame is released (by calling
chfl_frame%free()
), the pointer is released too.This function returns a Fortran pointer, which must be used in a pointer assignement context:
program example use iso_fortran_env, only: real64 use chemfiles implicit none type(chfl_frame) :: frame real(real64), pointer :: positions(:, :) call frame%init() call frame%resize(122) positions => frame%positions() call frame%free() end program
- Return:
real (3, :) [pointer]
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- function chfl_frame%velocities([status])¶
Get a pointer to the velocities array from the frame.
This function gives access to chemfiles internal data structure, and do not perform any copy, both when reading and writing the velocities.
- The pointer is invalidated if any of the following function is called:
When the memory of the frame is released (by calling
chfl_frame%free()
), the pointer is released too.This function returns a Fortran pointer, which must be used in a pointer assignement context:
program example use iso_fortran_env, only: real64 use chemfiles implicit none type(chfl_frame) :: frame real(real64), pointer :: velocities(:, :) call frame%init() call frame%resize(122) call frame%add_velocities() velocities => frame%velocities() call frame%free() end program
- Return:
real (3, :) [pointer]
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the 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(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- function chfl_frame%has_velocities([status])¶
Check if this frame contains velocity data.
- Return:
logical
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- function chfl_frame%cell([status])¶
Get access to the cell of this frame
Any modification to the cell will be reflected in the frame. The frame will be kept alive, even if
chfl_frame%free()
is called, untilchfl_cell%free()
is also called on the cell returned by this function.If
chfl_frame%set_cell()
is called, the cell returned by this function will point to the new cell.- Return:
type (chfl_cell)
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- subroutine chfl_frame%set_cell(cell[, status])¶
Set the
chfl_cell
of this frame tocell
.- Parameters:
cell [type(chfl_cell)] :: new unit cell of the frame
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- function chfl_frame%topology([status])¶
Get read-only access to the topology of this frame. Trying to write to the topology will give an error.
The frame will be kept alive, even if
chfl_frame%free()
is called, untilchfl_topology%free()
is also called on the topology returned by this function.If
chfl_frame%set_topology()
is called, the topology returned by this function will point to the new topology.- Return:
type (chfl_topology)
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- subroutine chfl_frame%set_topology(topology[, status])¶
Set the
chfl_topology
of this frame totopology
.Calling this function with a topology that does not contain the right number of atom will return an error.
- Parameters:
topology [type(chfl_topology)] :: new topology of the frame
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- function chfl_frame%step([status])¶
Get the frame step, i.e. the frame number in the trajectory.
- Return:
integer
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the 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(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- subroutine chfl_frame%guess_bonds([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(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- subroutine chfl_frame%set(name, property[, status])¶
Add a new
property
with the givenname
to this frame.If a property with the same name already exists, this function override the existing property with the new one.
property
can either be achfl_property
, or any value that can be stored in achfl_property
: logical, real, string, or vector3d.- Parameters:
name [character(len=*)] :: property name
property [type(chfl_property)] :: the new property
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- function chfl_frame%get(name[, status])¶
Get a copy of the property with the given
name
in this frame. If no property exist with this name,status
will be set toCHFL_PROPERTY_ERROR
.The associated memory must be released by calling
chfl_property%free()
.- Return:
type (chfl_property)
- Parameters:
name [character(len=*)] :: property name
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- function chfl_frame%properties_count([status])¶
Get the number of properties in this frame.
- Return:
integer
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- subroutine chfl_frame%list_properties(names[, status])¶
Fill the pre-allocated array
names
with the names of the properties in this frame. The array must have room forchfl_frame%properties_count()
values of typecharacter(len=CHFL_STRING_LENGTH)
.- Return:
integer
- Parameters:
names (:) [character(len=CHFL_STRING_LENGTH)] :: list of properties names
- Options:
status [integer(chfl_status)] :: status code of the operation. If it is not
CHFL_SUCCESS
, usechfl_last_error()
to learn more about the error.
- subroutine chfl_frame%free()¶
Destroy a frame, and free the associated memory