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

!> field grid types
module mimic_field_grids

    use mimic_cells
    use mimic_precision, only: dp

    implicit none

    private

    public :: real_field_grid_type
    public :: density_type
    public :: potential_type

    !> real field discretized on a grid
    type :: real_field_grid_type
        private
        integer, public :: id
        !> field values in grid points
        real(dp), dimension(:,:,:), pointer, public :: field => null()
    contains
        private
        procedure, public :: init => init_real_field_grid
    end type real_field_grid_type

    !> electronic density type
    type, extends(real_field_grid_type) :: density_type
        private
    contains
        private
    end type density_type

    !> external potential on an electronic grid
    type, extends(real_field_grid_type) :: potential_type
        private
    contains
        private
    end type potential_type

contains

subroutine init_real_field_grid(this, id, field)

    class(real_field_grid_type), intent(inout) :: this
    integer, intent(in) :: id
    real(dp), dimension(:,:,:), intent(in), target :: field

    this%id = id
    this%field => field

end subroutine init_real_field_grid

end module mimic_field_grids