atmcfg_t Derived Type

type, public :: atmcfg_t


Contents

Source Code


Components

TypeVisibility AttributesNameInitial
integer, public :: num_atom_types =0

Number of atom_types

character(len=8), public, dimension(:), allocatable:: atom_names

(num_atom_types,) array. Name of atoms of each type.

integer, public, dimension(:), allocatable:: atom_styles

(num_atom_types,) array. Style of atoms of each type.

real(kind=rp), public, dimension(:), allocatable:: atom_mass

(num_atom_types,) array. Mass of atoms of each type.

integer, public :: num_atoms =0

Number of atoms

integer, public, dimension(:), allocatable:: atoms

(num_atoms,) array.

For atom i, its type at = atoms(i), with style atom_styles(at), name atom_names(at), mass atom_mass(at), charge charge(i), position coordinates(:,i), velocity velocities(:,i), orientation (if the style requires) orientations(:,i). The force acting on atom i is forces(:,i).

real(kind=rp), public, dimension(:), allocatable:: charge

(num_atoms,) array.

real(kind=rp), public, dimension(:,:), allocatable:: coordinates

(3, num_atoms) array

real(kind=rp), public, dimension(:,:), allocatable:: forces

(3, num_atoms) array

integer, public :: num_bond_types =0

Number of bond_types

integer, public, dimension(:), allocatable:: bond_styles

(num_bond_types,) array.

real(kind=rp), public, dimension(:,:), allocatable:: bond_params

(mxparam,num_bond_types) array.

integer, public :: num_bonds =0

Total number of bonds.

integer, public, dimension(:,:), allocatable:: bonds

(3, num_bonds) array. Bond i is of type bt = bonds(1,i), directed from atom bonds(2,i) to bonds(3,i). Its style is bond_styles(bt) with parameters bond_params(:,bt).

integer, public :: num_angle_types =0

Number of angle_types

integer, public, dimension(:), allocatable:: angle_styles

(num_angle_types,) array

real(kind=rp), public, dimension(:,:), allocatable:: angle_params

(mxparam, num_angle_types) array

integer, public :: num_angles =0

Number of angles

integer, public, dimension(:,:), allocatable:: angles

(4, num_angles) array. Angle i is of type ant = angles(1,i), incident to atoms angles(2,i), angles(3,i), and angles(4,i). Its style is angle_styles(ant) with parameters angle_params(:,ant).

integer, public :: num_dihedral_types =0

Number of dihedral_types

integer, public, dimension(:), allocatable:: dihedral_styles

(num_dihedral_types,) array

real(kind=rp), public, dimension(:,:), allocatable:: dihedral_params

(mxparam, num_dihedral_types) array

integer, public :: num_dihedrals =0

Number of dihedrals

integer, public, dimension(:,:), allocatable:: dihedrals

(5, num_dihedrals) array. Dihedral i is of type dt = dihedrals(1,i), incident to atoms dihedrals(2,i), dihedrals(3,i), dihedrals(4,i), and dihedrals(5,i). Its style is dihedral_styles(dt) with parameters dihedral_params(:,dt).

integer, public :: num_branches =0

Total number of branches (including the backbone)

integer, public, dimension(:,:), allocatable:: branches

(3,num_branches) array. Branch i is tethered to atom branches(1,i), contains branches(2,i) atoms, with the beginning atom index branches(3,i).

integer, public :: num_molecule_types =0

Number of molecule_types

character(len=8), public, dimension(:), allocatable:: molecule_names

(num_molecule_types,) array

integer, public, dimension(:), allocatable:: molecule_pop

(num_molecule_types,) array

integer, public :: num_molecules =0

Number of molecules

integer, public, dimension(:,:), allocatable:: molecules

(9,num_molecules) array. For molecule i, its type mt = molecules(1,i), containing molecules(2,i) atoms with beginning index molecules(3,i), molecules(4,i) bonds with beginning index molecules(5,i), molecules(6,i) angles with beginning index molecules(7,i), and molecules(8,i) dihedrals with beginning index molecules(9,i).

real(kind=rp), public, dimension(3):: molecule_com =0.0_rp

Center of mass of the molecule. This is used only when imcon == 0, i.e. for a single molecule without periodic boundaries.

integer, public :: num_tether_types =0

Number of tether_types

integer, public, dimension(:), allocatable:: tether_styles

(num_tether_types,) array

real(kind=rp), public, dimension(:,:), allocatable:: tether_params

(mxparam, num_tether_types) array

integer, public :: num_tethers =0

Number of tethers

integer, public, dimension(:,:), allocatable:: tethers

(2, num_tethers) array. Tether i is of type tt = tethers(1,i), tethering atom tethers(2,i) to a point tether_points(:,i). Its style is tether_styles(tt) with parameters tether_params(:,tt).

real(kind=rp), public, dimension(:,:), allocatable:: tether_points

(3, num_tethers) array

integer, public :: num_vdw_types =0

Number of vdw_types

integer, public, dimension(:), allocatable:: vdw_styles

(num_vdw_types,) array

real(kind=rp), public, dimension(:,:), allocatable:: vdw_params

(mxparam, num_vdw_types) array

integer, public, dimension(:,:), allocatable:: vdw_pairs

(2, num_vdw_types) array. Stores atom type of interacting pairs, such that at_i >= at_j.

integer, public :: num_externals =0

Number of external fields

integer, public, dimension(:), allocatable:: external_styles

(num_external,) array

real(kind=rp), public, dimension(:,:), allocatable:: external_params

(mxparam, num_external) array

integer, public :: flow_style =0
real(kind=rp), public, dimension(:), allocatable:: flow_params

(mxparam,) array


Source Code

type atmcfg_t
    !Particle configuration: Atoms
    integer :: num_atom_types = 0
        !! Number of *atom_type*s
    character(len=8), dimension(:), allocatable :: atom_names
        !! (*num_atom_types*,) array. Name of atoms of each type.
    integer, dimension(:), allocatable :: atom_styles
        !! (*num_atom_types*,) array. Style of atoms of each type.
    real(rp), dimension(:), allocatable :: atom_mass
        !! (*num_atom_types*,) array. Mass of atoms of each type.
    integer :: num_atoms = 0
        !!  Number of atoms
    integer , dimension(:), allocatable:: atoms
        !! (*num_atoms*,) array. 
        !!
        !! For atom *i*, its type *at = atoms(i)*, with style
        !! *atom_styles(at)*, name *atom_names(at)*, mass *atom_mass(at)*, charge
        !! *charge(i)*, position *coordinates(:,i)*, velocity *velocities(:,i)*,
        !! orientation (if the style requires) *orientations(:,i)*. The force 
        !! acting on atom *i* is *forces(:,i)*.
    real(rp), dimension(:), allocatable :: charge
        !! (*num_atoms*,) array.
    real(rp), dimension(:,:), allocatable :: coordinates
        !!  (3, *num_atoms*) array
    real(rp), dimension(:,:), allocatable :: forces
        !!  (3, *num_atoms*) array
    
    !Particle configuration: Bonds
    integer :: num_bond_types = 0
        !!  Number of *bond_type*s
    integer, dimension(:), allocatable :: bond_styles
        !!  (*num_bond_types*,) array.
    real(rp), dimension(:,:), allocatable :: bond_params
        !!  (*mxparam*,*num_bond_types*) array.
    integer :: num_bonds = 0
        !!  Total number of bonds.
    integer, dimension(:,:), allocatable :: bonds
        !! (3, *num_bonds*) array. Bond *i* is of type *bt = bonds(1,i)*,  directed from
        !! atom *bonds(2,i)* to *bonds(3,i)*. Its style is *bond_styles(bt)* with
        !! parameters *bond_params(:,bt)*.
    
    !Particle configuration: Angles
    integer :: num_angle_types = 0
        !!  Number of *angle_type*s
    integer, dimension(:), allocatable :: angle_styles
        !!  (*num_angle_types*,) array
    real(rp), dimension(:,:), allocatable :: angle_params
        !!  (*mxparam*, *num_angle_types*) array
    integer :: num_angles = 0
        !!  Number of angles
    integer, dimension(:,:), allocatable :: angles
        !! (4, *num_angles*) array. Angle *i* is of type *ant = angles(1,i)*, incident
        !! to atoms *angles(2,i)*, *angles(3,i)*, and *angles(4,i)*. Its style is
        !! *angle_styles(ant)* with parameters *angle_params(:,ant)*.
    
    !Particle configuration: Dihedrals
    integer :: num_dihedral_types = 0
        !!  Number of *dihedral_type*s
    integer, dimension(:), allocatable :: dihedral_styles
        !!  (*num_dihedral_types*,) array
    real(rp), dimension(:,:), allocatable :: dihedral_params
        !!  (*mxparam*, *num_dihedral_types*) array
    integer :: num_dihedrals = 0
        !!  Number of dihedrals
    integer, dimension(:,:), allocatable :: dihedrals
        !! (5, *num_dihedrals*) array. Dihedral *i* is of type *dt = dihedrals(1,i)*, incident
        !! to atoms *dihedrals(2,i)*, *dihedrals(3,i)*, *dihedrals(4,i)*, and *dihedrals(5,i)*.
        !! Its style is *dihedral_styles(dt)* with parameters *dihedral_params(:,dt)*.
    
    !Particle configuration: Branches
    integer :: num_branches = 0
        !! Total number of branches (including the backbone)
    integer , dimension(:,:), allocatable:: branches
        !! (3,*num_branches*) array. Branch *i* is tethered to atom *branches(1,i)*,
        !! contains *branches(2,i)* atoms, with the beginning atom index *branches(3,i)*.
    
    !Particle configuration: Molecules
    integer :: num_molecule_types = 0
        !!  Number of *molecule_type*s
    character(len=8), dimension(:), allocatable :: molecule_names
        !! (*num_molecule_types*,) array
    integer, dimension(:), allocatable :: molecule_pop
        !! (*num_molecule_types*,) array
    integer :: num_molecules = 0
        !!  Number of molecules
    integer, dimension(:,:), allocatable :: molecules
        !! (9,*num_molecules*) array. For molecule *i*, its type *mt = molecules(1,i)*, 
        !! containing *molecules(2,i)* atoms with beginning index *molecules(3,i)*,
        !! *molecules(4,i)* bonds with beginning index *molecules(5,i)*,
        !! *molecules(6,i)* angles with beginning index *molecules(7,i)*, and
        !! *molecules(8,i)* dihedrals with beginning index *molecules(9,i)*.
    real(rp), dimension(3) :: molecule_com = 0.0_rp
        !! Center of mass of the molecule. This is used only when imcon == 0, i.e.
        !! for a single molecule without periodic boundaries.
    
    !Particle configuration: Tethers
    integer :: num_tether_types = 0
        !!  Number of *tether_type*s
    integer, dimension(:), allocatable :: tether_styles
        !!  (*num_tether_types*,) array
    real(rp), dimension(:,:), allocatable :: tether_params
        !!  (*mxparam*, *num_tether_types*) array
    integer :: num_tethers = 0
        !!  Number of tethers
    integer, dimension(:,:), allocatable :: tethers
        !! (2, *num_tethers*) array. Tether *i* is of type *tt = tethers(1,i)*, tethering
        !! atom *tethers(2,i)* to a point *tether_points(:,i)*.
        !! Its style is *tether_styles(tt)* with parameters *tether_params(:,tt)*.
    real(rp), dimension(:,:), allocatable :: tether_points
        !!  (3, *num_tethers*) array
    
    !Particle configuration: VDW (pair) interactions
    integer :: num_vdw_types = 0
        !!  Number of *vdw_type*s
    integer, dimension(:), allocatable :: vdw_styles
        !!  (*num_vdw_types*,) array
    real(rp), dimension(:,:), allocatable :: vdw_params
        !!  (*mxparam*, *num_vdw_types*) array
    integer, dimension(:,:), allocatable :: vdw_pairs
        !!  (2, *num_vdw_types*) array. Stores atom type of interacting pairs, such
        !! that at_i >= at_j.
    
    !Particle configuration: External force field
    integer :: num_externals = 0
        !!  Number of external fields
    integer, dimension(:), allocatable :: external_styles
        !!  (*num_external*,) array
    real(rp), dimension(:,:), allocatable :: external_params
        !!  (*mxparam*, *num_external*) array
    
    !Particle configuration: Flow field
    integer :: flow_style = 0
    real(rp), dimension(:), allocatable :: flow_params
        !!  (*mxparam*,) array
end type atmcfg_t