mimic_subsystems.f90 Source File


Contents

Source Code


Source Code

!
!    MiMiC: A Framework for Multiscale Modeling in Computational Chemistry
!    Copyright (C) 2015-2022  The MiMiC Contributors (see CONTRIBUTORS file for details).
!
!    This file is part of MiMiC.
!
!    MiMiC is free software: you can redistribute it and/or modify
!    it under the terms of the GNU Lesser General Public License as
!    published by the Free Software Foundation, either version 3 of
!    the License, or (at your option) any later version.
!
!    MiMiC is distributed in the hope that it will be useful, but
!    WITHOUT ANY WARRANTY; without even the implied warranty of
!    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
!    GNU Lesser General Public License for more details.
!
!    You should have received a copy of the GNU Lesser General Public License
!    along with this program.  If not, see <http://www.gnu.org/licenses/>.
!

!> fragment types
module mimic_subsystems

    use mimic_fragments
    use mimic_particles
    use mimic_precision, only: dp

    implicit none

    private

    public :: subsystem_type

    !> subsystem which is a collection of atoms
    type :: subsystem_type
        private
        !> ID of the code
        integer, public :: id
        !> factor to be applied for forces contribution
        !> (most likely to be either 1.0 or -1.0)
        real(dp), public :: factor
        !> total number of atoms within subsystem
        integer, public :: num_atoms
        !> list of atoms
        type(atom_type), dimension(:), allocatable, public :: atoms
        !> total number of fragments within subsystem
        integer, public :: num_fragments
        !> list of fragments in within subsystem
        type(fragment_type), dimension(:), allocatable, public :: fragments
        !> number of short-range atoms
        integer, public :: num_sr_atoms
        !> list of short-range atoms
        type(atom_type), dimension(:), allocatable, public :: sr_atoms
        !> number of short-range fragments
        integer, public :: num_sr_fragments
        !> list of short-range fragments
        type(fragment_type), dimension(:), allocatable, public :: sr_fragments
        !> number of long-range atoms
        integer, public :: num_lr_atoms
        !> list of long-range atoms
        type(atom_type), dimension(:), allocatable, public :: lr_atoms
        !> number of long-range fragments
        integer, public :: num_lr_fragments
        !> list of long-range fragments
        type(fragment_type), dimension(:), allocatable, public :: lr_fragments
    contains
        private
        procedure, public :: init => init_subsystem
        procedure, public :: define_fragments
    end type subsystem_type

contains

subroutine init_subsystem(this, id, factor, atoms)

    class(subsystem_type), intent(inout) :: this
    integer, intent(in) :: id
    real(dp), intent(in) :: factor
    type(atom_type), dimension(:), intent(in) :: atoms

    this%id = id
    this%factor = factor
    this%num_atoms = size(atoms)
    allocate(this%atoms(this%num_atoms))
    this%atoms = atoms
    this%num_fragments = -1

end subroutine init_subsystem

subroutine define_fragments(this, num_fragments, fragment_definitions)

    class(subsystem_type), intent(inout) :: this
    integer, intent(in) :: num_fragments
    integer, dimension(0:num_fragments), intent(in) :: fragment_definitions

    integer :: i, j, k

    this%num_fragments = num_fragments

    allocate(this%fragments(this%num_fragments))

    do i = 1, this%num_fragments
        j = fragment_definitions(i-1) + 1
        k = fragment_definitions(i)
        call this%fragments(i)%init(i, this%atoms(j:k))
    end do

end subroutine define_fragments

end module mimic_subsystems