Skip to content

Commit

Permalink
Added unit test for MortarInit() for variable polynomial degrees up t…
Browse files Browse the repository at this point in the history
…o 50.
  • Loading branch information
scopplestone committed Jun 6, 2023
1 parent 9860da2 commit 61bd536
Show file tree
Hide file tree
Showing 5 changed files with 70 additions and 9 deletions.
13 changes: 9 additions & 4 deletions src/interpolation/interpolation.f90
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,7 @@ SUBROUTINE DefineParametersInterpolation()
END SUBROUTINE DefineParametersInterpolation


SUBROUTINE InitInterpolation(NIn)
SUBROUTINE InitInterpolation(NIn,NAnalyzeIn)
!============================================================================================================================
! Initialize basis for Gauss-points of order N.
! Prepares Differentiation matrices D, D_Hat, Basis at the boundaries L(1), L(-1), L_Hat(1), L_Hat(-1)
Expand All @@ -113,7 +113,8 @@ SUBROUTINE InitInterpolation(NIn)
IMPLICIT NONE
!----------------------------------------------------------------------------------------------------------------------------
!input parameters
INTEGER,INTENT(IN),OPTIONAL :: NIn !< optional polynomial degree
INTEGER,INTENT(IN),OPTIONAL :: NIn !< optional polynomial degree
INTEGER,INTENT(IN),OPTIONAL :: NAnalyzeIn !< optional analyze polynomial degree
!----------------------------------------------------------------------------------------------------------------------------
!output parameters
!----------------------------------------------------------------------------------------------------------------------------
Expand Down Expand Up @@ -149,8 +150,12 @@ SUBROUTINE InitInterpolation(NIn)
CALL InitInterpolationBasis(PP_N, xGP, wGP, wBary, L_Minus , L_Plus, L_PlusMinus, swGP=swGP, wGPSurf=wGPSurf)

! Set the default analyze polynomial degree NAnalyze to 2*(N+1)
WRITE(DefStr,'(i4)') 2*(PP_N+1)
NAnalyze = GETINT('NAnalyze',DefStr)
IF(PRESENT(NAnalyzeIn))THEN
NAnalyze = NAnalyzeIn
ELSE
WRITE(DefStr,'(i4)') 2*(PP_N+1)
NAnalyze = GETINT('NAnalyze',DefStr)
END IF ! PRESENT(NAnalyzeIn)

! Initialize the basis functions for the analyze polynomial
CALL InitAnalyzeBasis(PP_N,NAnalyze,xGP,wBary)
Expand Down
1 change: 0 additions & 1 deletion src/mortar/mortar.f90
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,6 @@ SUBROUTINE InitMortar()
! Basic Mortar initialization.
!===================================================================================================================================
! MODULES
USE MOD_Globals
USE MOD_Preproc
USE MOD_Globals
USE MOD_Interpolation_Vars ,ONLY: InterpolationInitIsDone,NodeType
Expand Down
1 change: 1 addition & 0 deletions unitTests/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,7 @@ MESSAGE(STATUS "Executing unit tests with $ENV{CTEST_PARALLEL_LEVEL} processes")
# Add the unit tests
add_unit_test(ReadInTools ./unitTests/ReadInTools.f90)
add_unit_test(MatrixInverse ./unitTests/MatrixInverse.f90)
add_unit_test(MortarBasis ./unitTests/MortarBasis.f90)
#add_unit_test(NodesAndWeights ./unitTests/NodesAndWeights.f90)
#add_unit_test(Vandermonde ./unitTests/Vandermonde.f90)
#add_unit_test(DerivativeMatrix ./unitTests/DerivativeMatrix.f90)
Expand Down
8 changes: 4 additions & 4 deletions unitTests/MatrixInverse.f90
Original file line number Diff line number Diff line change
Expand Up @@ -13,10 +13,10 @@
#include "piclas.h"

!==================================================================================================================================
!> Unit test 'ReadInToolsUnitTest'
!> Test the module: MOD_ReadInTools
!> Unit test 'MatrixInverseUnitTest'
!> Test the functions: INVERSE_LU, getSPDInverse
!==================================================================================================================================
PROGRAM ReadInToolsUnitTest
PROGRAM MatrixInverseUnitTest
! MODULES
USE MOD_Globals
USE MOD_ReadInTools
Expand Down Expand Up @@ -220,4 +220,4 @@ PROGRAM ReadInToolsUnitTest
IF(iError.NE.0) CALL abort(__STAMP__,'MPI finalize error')
#endif

END PROGRAM ReadInToolsUnitTest
END PROGRAM MatrixInverseUnitTest
56 changes: 56 additions & 0 deletions unitTests/MortarBasis.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,56 @@
!==================================================================================================================================
! Copyright (c) 2023 Stephen M. Copplestone, Patrick Kopper
!
! This file is part of PICLas (piclas.boltzplatz.eu/piclas/piclas). PICLas is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3
! of the License, or (at your option) any later version.
!
! PICLas 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 v3.0 for more details.
!
! You should have received a copy of the GNU General Public License along with PICLas. If not, see <http://www.gnu.org/licenses/>.
!==================================================================================================================================
#include "piclas.h"

!==================================================================================================================================
!> Unit test 'MortarBasisUnitTest'
!> Test the module: MOD_Mortar, function InitMortar
!==================================================================================================================================
PROGRAM MortarBasisUnitTest
! MODULES
USE MOD_Globals
USE MOD_Preproc
USE MOD_Mortar ,ONLY: InitMortar,FinalizeMortar
USE MOD_MPI ,ONLY: InitMPI
USE MOD_Interpolation ,ONLY: InitInterpolation,FinalizeInterpolation
IMPLICIT NONE
!----------------------------------------------------------------------------------------------------------------------------------
! LOCAL VARIABLES
INTEGER :: nArgs,i
INTEGER,PARAMETER :: MaxPolDeg=50
!==================================================================================================================================
CALL InitMPI()
! Check for command line arguments to generate the reference solution
nArgs=COMMAND_ARGUMENT_COUNT()
IF (nArgs.GT.0) CALL abort(__STAMP__,'ERROR - Unknown command line argument.')

#if PP_N == N
DO i = 1, MaxPolDeg
PP_N = i
#endif
WRITE(*,'(A,I0)') " Testing MortarInit for N = ",PP_N
CALL InitInterpolation(PP_N,2*(PP_N+1))
CALL InitMortar()
CALL FinalizeMortar()
CALL FinalizeInterpolation()
#if PP_N == N
END DO ! i = 1, MaxPolDeg
#endif

#if USE_MPI
! we also have to finalize MPI itself here
CALL MPI_FINALIZE(iError)
IF(iError.NE.0) CALL abort(__STAMP__,'MPI finalize error')
#endif

END PROGRAM MortarBasisUnitTest

0 comments on commit 61bd536

Please sign in to comment.