!> !> @file conmat.f90 !> !> @brief !> !> @copyright !> Copyright (©) 2021 EPFL (Ecole Polytechnique Fédérale de Lausanne) !> SPC (Swiss Plasma Center) !> !> spclibs 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. !> !> spclibs 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 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 . !> !> @authors !> (in alphabetical order) !> @author Trach-Minh Tran !> MODULE conmat_mod ! ! CONMAT: Matrix construction for FE discretization. ! ! T.M. Tran, CRPP-EPFL ! November 2011 ! USE bsplines USE matrix #ifdef MKL USE pardiso_bsplines #endif IMPLICIT NONE ! INTERFACE conrhs MODULE PROCEDURE conrhs_r, conrhs_z END INTERFACE conrhs INTERFACE conmat MODULE PROCEDURE conmat_1d_gb, conmat_1d_ge, conmat_1d_pb, conmat_1d_periodic, & & conmat_1d_zgb, conmat_1d_zpb, conmat_1d_zperiodic, & & conmat_gb, conmat_pb, & & conmat_zgb, conmat_zpb END INTERFACE conmat #ifdef MKL INTERFACE conmat MODULE PROCEDURE conmat_1d_pardiso, conmat_1d_zpardiso, & & conmat_pardiso, conmat_zpardiso END INTERFACE conmat #endif ! CONTAINS !=========================================================================== SUBROUTINE conmat_1d_gb(spl, mat, coefeq, maxder) ! ! Construction of FE matrix mat for 1D differential operator ! using spline spl ! TYPE(gbmat) :: mat TYPE(spline1d), INTENT(in) :: spl ! INCLUDE 'conmat_1d.tpl' END SUBROUTINE conmat_1d_gb !=========================================================================== SUBROUTINE conmat_1d_ge(spl, mat, coefeq, maxder) ! ! Construction of FE matrix mat for 1D differential operator ! using spline spl ! TYPE(gemat) :: mat TYPE(spline1d), INTENT(in) :: spl ! INCLUDE 'conmat_1d.tpl' END SUBROUTINE conmat_1d_ge !=========================================================================== SUBROUTINE conmat_1d_pb(spl, mat, coefeq, maxder) ! ! Construction of FE matrix mat for 1D differential operator ! using spline spl ! TYPE(pbmat) :: mat TYPE(spline1d), INTENT(in) :: spl ! INCLUDE 'conmat_1d.tpl' END SUBROUTINE conmat_1d_pb !=========================================================================== SUBROUTINE conmat_1d_periodic(spl, mat, coefeq, maxder) ! ! Construction of FE matrix mat for 1D differential operator ! using spline spl ! TYPE(periodic_mat) :: mat TYPE(spline1d), INTENT(in) :: spl ! INCLUDE 'conmat_1d.tpl' END SUBROUTINE conmat_1d_periodic !=========================================================================== SUBROUTINE conmat_1d_zgb(spl, mat, coefeq, maxder) ! ! Construction of FE matrix mat for 1D differential operator ! using spline spl ! TYPE(zgbmat) :: mat TYPE(spline1d), INTENT(in) :: spl ! INCLUDE 'zconmat_1d.tpl' END SUBROUTINE conmat_1d_zgb !=========================================================================== SUBROUTINE conmat_1d_zpb(spl, mat, coefeq, maxder) ! ! Construction of FE matrix mat for 1D differential operator ! using spline spl ! TYPE(zpbmat) :: mat TYPE(spline1d), INTENT(in) :: spl ! INCLUDE 'zconmat_1d.tpl' END SUBROUTINE conmat_1d_zpb !=========================================================================== SUBROUTINE conmat_1d_zperiodic(spl, mat, coefeq, maxder) ! ! Construction of FE matrix mat for 1D differential operator ! using spline spl ! TYPE(zperiodic_mat) :: mat TYPE(spline1d), INTENT(in) :: spl ! INCLUDE 'zconmat_1d.tpl' END SUBROUTINE conmat_1d_zperiodic !=========================================================================== SUBROUTINE conmat_gb(spl, mat, coefeq, maxder, nat_order) ! ! Construction of FE matrix mat for 2D differential operator ! using spline spl ! TYPE(gbmat) :: mat TYPE(spline2d), INTENT(in) :: spl ! INCLUDE 'conmat.tpl' END SUBROUTINE conmat_gb !=========================================================================== SUBROUTINE conmat_pb(spl, mat, coefeq, maxder, nat_order) ! ! Construction of FE matrix mat for 2D differential operator ! using spline spl ! TYPE(pbmat) :: mat TYPE(spline2d), INTENT(in) :: spl ! INCLUDE 'conmat.tpl' END SUBROUTINE conmat_pb !=========================================================================== SUBROUTINE conmat_zgb(spl, mat, coefeq, maxder, nat_order) ! ! Construction of FE matrix mat for 2D differential operator ! using spline spl ! TYPE(zgbmat) :: mat TYPE(spline2d), INTENT(in) :: spl ! INCLUDE 'zconmat.tpl' END SUBROUTINE conmat_zgb !=========================================================================== SUBROUTINE conmat_zpb(spl, mat, coefeq, maxder, nat_order) ! ! Construction of FE matrix mat for 2D differential operator ! using spline spl ! TYPE(zpbmat) :: mat TYPE(spline2d), INTENT(in) :: spl ! INCLUDE 'zconmat.tpl' END SUBROUTINE conmat_zpb !=========================================================================== SUBROUTINE conrhs_r(spl, farr, frhs) ! ! Projection of RHS on spline basis functions ! TYPE(spline1d) :: spl DOUBLE PRECISION, INTENT(out) :: farr(:) INTERFACE DOUBLE PRECISION FUNCTION frhs(x) DOUBLE PRECISION, INTENT(in) :: x END FUNCTION frhs END INTERFACE DOUBLE PRECISION :: contrib ! INCLUDE 'conrhs.tpl' END SUBROUTINE conrhs_r !=========================================================================== SUBROUTINE conrhs_z(spl, farr, frhs) ! ! Projection of RHS on spline basis functions ! TYPE(spline1d) :: spl DOUBLE COMPLEX, INTENT(out) :: farr(:) INTERFACE DOUBLE COMPLEX FUNCTION frhs(x) DOUBLE PRECISION, INTENT(in) :: x END FUNCTION frhs END INTERFACE DOUBLE COMPLEX :: contrib ! INCLUDE 'conrhs.tpl' END SUBROUTINE conrhs_z !=========================================================================== #ifdef MKL SUBROUTINE conmat_1d_pardiso(spl, mat, coefeq, maxder) ! ! Construction of FE matrix mat for 1D differential operator ! using spline spl ! TYPE(pardiso_mat) :: mat TYPE(spline1d), INTENT(in) :: spl ! INCLUDE 'conmat_1d.tpl' END SUBROUTINE conmat_1d_pardiso !=========================================================================== SUBROUTINE conmat_1d_zpardiso(spl, mat, coefeq, maxder) ! ! Construction of FE matrix mat for 1D differential operator ! using spline spl ! TYPE(zpardiso_mat) :: mat TYPE(spline1d), INTENT(in) :: spl ! INCLUDE 'zconmat_1d.tpl' END SUBROUTINE conmat_1d_zpardiso !=========================================================================== SUBROUTINE conmat_pardiso(spl, mat, coefeq, maxder, nat_order) ! ! Construction of FE matrix mat for 2D differential operator ! using spline spl ! TYPE(pardiso_mat) :: mat TYPE(spline2d), INTENT(in) :: spl ! INCLUDE 'conmat.tpl' END SUBROUTINE conmat_pardiso !=========================================================================== SUBROUTINE conmat_zpardiso(spl, mat, coefeq, maxder, nat_order) ! ! Construction of FE matrix mat for 2D differential operator ! using spline spl ! TYPE(zpardiso_mat) :: mat TYPE(spline2d), INTENT(in) :: spl ! INCLUDE 'zconmat.tpl' END SUBROUTINE conmat_zpardiso !=========================================================================== #endif END MODULE conmat_mod