Skip to content

Commit

Permalink
BR2 and tests fixed
Browse files Browse the repository at this point in the history
  • Loading branch information
Dhueper committed Nov 8, 2024
1 parent 377baad commit ea3caa8
Show file tree
Hide file tree
Showing 3 changed files with 11 additions and 11 deletions.
6 changes: 3 additions & 3 deletions Solver/src/libs/discretization/EllipticBR2.f90
Original file line number Diff line number Diff line change
Expand Up @@ -430,9 +430,9 @@ subroutine BR2_ComputeGradientFaceIntegrals( self, nGradEqn, e, mesh)
unStar => mesh % faces(e % faceIDs(EBOTTOM)) % storage(e % faceSide(EBOTTOM)) % unStar )

do k = 0, e%Nxyz(3) ; do j = 0, e%Nxyz(2) ; do i = 0, e%Nxyz(1)
U_x(:,i,j) = U_x(:,i,j) - self % eta * unStar(:,1,i,j) * bv_z(k,LEFT) * invjac(i,i,j)
U_y(:,i,j) = U_y(:,i,j) - self % eta * unStar(:,2,i,j) * bv_z(k,LEFT) * invjac(i,i,j)
U_z(:,i,j) = U_z(:,i,j) - self % eta * unStar(:,3,i,j) * bv_z(k,LEFT) * invjac(i,i,j)
U_x(:,i,j) = U_x(:,i,j) - self % eta * unStar(:,1,i,j) * bv_z(k,LEFT) * invjac(i,j,k)
U_y(:,i,j) = U_y(:,i,j) - self % eta * unStar(:,2,i,j) * bv_z(k,LEFT) * invjac(i,j,k)
U_z(:,i,j) = U_z(:,i,j) - self % eta * unStar(:,3,i,j) * bv_z(k,LEFT) * invjac(i,j,k)
end do ; end do ; end do
end associate

Expand Down
14 changes: 7 additions & 7 deletions Solver/test/NavierStokes/CylinderBR2/SETUP/ProblemFile.f90
Original file line number Diff line number Diff line change
Expand Up @@ -552,16 +552,16 @@ SUBROUTINE UserDefinedFinalize(mesh, time, iter, maxResidual &
!
#if defined(NAVIERSTOKES)
INTEGER :: iterations(3:7) = [100, 0, 0, 0, 0]
real(kind=RP), parameter :: residuals(5) = [ 8.94947477740774_RP, &
18.0524814828053_RP, &
0.188804475468846_RP, &
24.2331142737927_RP, &
244.034603817743_RP ]
real(kind=RP), parameter :: residuals(5) = [ 8.9494751074667516_RP, &
18.052481444063439_RP, &
0.1887988263729878_RP, &
24.233109718227368_RP, &
244.03459342403502_RP ]


real(kind=RP), parameter :: wake_u = 8.381270411983929E-009_RP
real(kind=RP), parameter :: cd = 34.3031214698872_RP
real(kind=RP), parameter :: cl = -5.536320494302416E-003_RP
real(kind=RP), parameter :: cd = 34.303121634815788_RP
real(kind=RP), parameter :: cl = -5.536315782160184E-003_RP

N = mesh % elements(1) % Nxyz(1) ! This works here because all the elements have the same order in all directions
CALL initializeSharedAssertionsManager
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -524,7 +524,7 @@ SUBROUTINE UserDefinedFinalize(mesh, time, iter, maxResidual &
! Local variables
! ---------------
!
CHARACTER(LEN=29) :: testName = "Re 200 Cylinder with Ducros Skewsymmetric and BR2"
CHARACTER(LEN=29) :: testName = "Re 200 Cylinder with Ducros Skewsymmetric and BR1"
REAL(KIND=RP) :: maxError
REAL(KIND=RP), ALLOCATABLE :: QExpected(:,:,:,:)
INTEGER :: eID
Expand Down

0 comments on commit ea3caa8

Please sign in to comment.