mimic_properties.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/>.
!

!> property types
module mimic_properties

    use mimic_precision, only: dp

    implicit none

    private

    public :: multipoles_type

    !> contains multipoles and related variables and procedures
    type :: multipoles_type
        private
        !> probably redundant
        integer, public :: id
        !> highest order of multipoles
        integer, public :: order
        !> coordinates of multipoles origin
        real(dp), dimension(3), public :: origin
        !> array of multipole values
        real(dp), dimension(:), allocatable, public :: values
    contains
        private
        procedure :: init_multipoles
        generic, public :: init => init_multipoles
        procedure, public :: get_size => get_multipoles_size
    end type multipoles_type

contains

subroutine init_multipoles(this, id, origin, order, values)

    class(multipoles_type), intent(inout) :: this
    integer, intent(in) :: id
    real(dp), dimension(:), intent(in) :: origin
    integer, intent(in) :: order
    real(dp), dimension(:), intent(in) :: values

    if (allocated(this%values)) then
        deallocate(this%values)
    end if
    allocate(this%values(size(values)))

    this%id = id
    this%origin = origin
    this%order = order
    this%values = values

end subroutine init_multipoles

pure integer function get_multipoles_size(this)

    class(multipoles_type), intent(in) :: this

    get_multipoles_size = (this%order + 3) * (this%order + 2) * (this%order + 1) / 6

end function get_multipoles_size

end module mimic_properties