Skip to content

Commit

Permalink
Update FaceClass.f90
Browse files Browse the repository at this point in the history
  • Loading branch information
HatemKsr committed Jun 29, 2024
1 parent 342c198 commit 8a61f6c
Showing 1 changed file with 17 additions and 17 deletions.
34 changes: 17 additions & 17 deletions Solver/src/libs/mesh/FaceClass.f90
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ Module FaceClass
type(FaceStorage_t) :: storage(2)
integer :: n_mpi_mortar
real(kind=RP) :: offset(2)
real(kind=RP) :: scale(2)
real(kind=RP) :: s(2)

contains
procedure :: Construct => ConstructFace
Expand Down Expand Up @@ -201,14 +201,14 @@ end SUBROUTINE PrintFace
!
!////////////////////////////////////////////////////////////////////////
!
SUBROUTINE Face_LinkWithElements( self, NelLeft, NelRight, nodeType, offset, scale)
SUBROUTINE Face_LinkWithElements( self, NelLeft, NelRight, nodeType, offset, s)
IMPLICIT NONE
class(Face) , intent(INOUT) :: self ! Current face
integer, intent(in) :: NelLeft(2) ! Left element face polynomial order
integer, intent(in) :: NelRight(2) ! Right element face polynomial order
integer, intent(in) :: nodeType ! Either Gauss or Gauss-Lobatto
real(kind=RP), optional, intent(in) :: offset(2)
real(kind=RP), optional, intent(in) :: scale
real(kind=RP), optional, intent(in) :: s(2)

!real(kind=RP) :: test1(0:3)
!real(kind=RP) :: test2(0:3)
Expand Down Expand Up @@ -284,7 +284,7 @@ SUBROUTINE Face_LinkWithElements( self, NelLeft, NelRight, nodeType, offset, sca
call Tset(self % Nf(2), self % NfLeft(2)) % construct(self % Nf(2), self % NfLeft(2))

end if
if (present(offset) .and. (.not.present(scale))) then
if (present(offset) .and. (.not.present(s))) then
call TsetM(self % NfLeft(1), self % Nf(1), 2, 1) % construct(self % NfLeft(1), self % Nf(1), 0.5_RP, 0.5_RP, 1)
call TsetM(self % Nf(1), self % NfLeft(1), 2, 2) % construct(self % Nf(1), self % NfLeft(1), 0.5_RP, 0.5_RP, 2)

Expand All @@ -298,18 +298,18 @@ SUBROUTINE Face_LinkWithElements( self, NelLeft, NelRight, nodeType, offset, sca
call TsetM(self % Nf(2), self % NfLeft(2), 1, 2) % construct(self % Nf(2), self % NfLeft(2), -0.5_RP, 0.5_RP, 2)
end if
if (present(offset) .and. present(scale)) then
if (MOD(f% ID, 2)==1) then
call TsetM(self % NfLeft(1), self % Nf(1), 1, 1) % construct(self % NfLeft(1), self % Nf(1), offset(1), scale(1), 1)
call TsetM(self % Nf(1), self % NfLeft(1), 1, 2) % construct(self % Nf(1), self % NfLeft(1), offset(1), scale(1), 2)

call TsetM(self % NfLeft(1), self % Nf(1), 2, 1) % construct(self % NfLeft(1), self % Nf(1), offset(2), scale(2), 1)
call TsetM(self % Nf(1), self % NfLeft(1), 2, 2) % construct(self % Nf(1), self % NfLeft(1), offset(2), scale(2), 2)
else if (MOD(f% ID, 2)==0)
call TsetM(self % NfLeft(1), self % Nf(1), 3, 1) % construct(self % NfLeft(1), self % Nf(1), offset(1), scale(1), 1)
call TsetM(self % Nf(1), self % NfLeft(1), 3, 2) % construct(self % Nf(1), self % NfLeft(1), offset(1), scale(1), 2)

call TsetM(self % NfLeft(1), self % Nf(1), 4, 1) % construct(self % NfLeft(1), self % Nf(1), offset(2), scale(2), 1)
call TsetM(self % Nf(1), self % NfLeft(1), 4, 2) % construct(self % Nf(1), self % NfLeft(1), offset(2), scale(2), 2)
if (MOD(self% ID, 2)==1) then
call TsetM(self % NfLeft(1), self % Nf(1), 1, 1) % construct(self % NfLeft(1), self % Nf(1), offset(1), s(1), 1)
call TsetM(self % Nf(1), self % NfLeft(1), 1, 2) % construct(self % Nf(1), self % NfLeft(1), offset(1), s(1), 2)

call TsetM(self % NfLeft(1), self % Nf(1), 2, 1) % construct(self % NfLeft(1), self % Nf(1), offset(2), s(2), 1)
call TsetM(self % Nf(1), self % NfLeft(1), 2, 2) % construct(self % Nf(1), self % NfLeft(1), offset(2), s(2), 2)
else if (MOD(self% ID, 2)==0)
call TsetM(self % NfLeft(1), self % Nf(1), 3, 1) % construct(self % NfLeft(1), self % Nf(1), offset(1), s(1), 1)
call TsetM(self % Nf(1), self % NfLeft(1), 3, 2) % construct(self % Nf(1), self % NfLeft(1), offset(1), s(1), 2)

call TsetM(self % NfLeft(1), self % Nf(1), 4, 1) % construct(self % NfLeft(1), self % Nf(1), offset(2), s(2), 1)
call TsetM(self % Nf(1), self % NfLeft(1), 4, 2) % construct(self % Nf(1), self % NfLeft(1), offset(2), s(2), 2)
end if
end if

Expand Down Expand Up @@ -1483,7 +1483,7 @@ subroutine Face_Interpolatebig2small(self, nEqn, fma, grad)
MInt(:,:,2)=(TsetM(fma % NfLeft(2), fma % Nf(2), 1, 1) % T)
case (2)
MInt(:,:,1)=(TsetM(fma % NfLeft(1), fma % Nf(1), 2, 1) % T)
MInt(:,:,2)=(TsetM(fma % NfLeft(), fma % Nf(2), 1, 1) % T)
MInt(:,:,2)=(TsetM(fma % NfLeft(2), fma % Nf(2), 1, 1) % T)
case (3)
MInt(:,:,1)=(TsetM(fma % NfLeft(1), fma % Nf(1), 1, 1) % T)
MInt(:,:,2)=(TsetM(fma % NfLeft(2), fma % Nf(2), 2, 1) % T)
Expand Down

0 comments on commit 8a61f6c

Please sign in to comment.