Skip to content

Commit

Permalink
dump on every funct3d call: debugging messages
Browse files Browse the repository at this point in the history
  • Loading branch information
jons-pf committed Oct 23, 2024
1 parent 2de809a commit d93018b
Show file tree
Hide file tree
Showing 2 changed files with 24 additions and 4 deletions.
24 changes: 20 additions & 4 deletions Sources/General/funct3d.f
Original file line number Diff line number Diff line change
Expand Up @@ -164,6 +164,8 @@ SUBROUTINE funct3d_par (lscreen, ier_flag)
ELSE IF (iter2 .EQ. iter1 .AND.
& ivac .LE. 0 .AND.
& ictrl_prec2d .EQ. 0) THEN
print *, "extrapolate (r,z)con into volume"

#if defined(MPI_OPT)
ALLOCATE(bcastbuf(2*nznt))
bcastbuf(1:nznt)=prcon(:,ns,0)
Expand All @@ -188,6 +190,10 @@ SUBROUTINE funct3d_par (lscreen, ier_flag)
!
CALL jacobian_par

IF (irst.EQ.2 .AND. iequi.EQ.0) THEN
print *, "bad Jacobian -- early return from funct3d"
end if

! COMPUTE COVARIANT COMPONENTS OF B, MAGNETIC AND KINETIC
! PRESSURE, AND METRIC ELEMENTS ON HALF-GRID

Expand Down Expand Up @@ -227,14 +233,18 @@ SUBROUTINE funct3d_par (lscreen, ier_flag)
& iter2 .GT. 1 .AND.
& iequi .EQ. 0) THEN

IF (ictrl_prec2d.LE.1 .AND. (fsqr + fsqz).LE.1.e-3_dp)
& ivac = ivac+1 !decreased from e-1 to e-3 - sph12/04
IF (ictrl_prec2d.LE.1 .AND. (fsqr + fsqz).LE.1.e-3_dp) THEN
print *, "activate Nestor"
ivac = ivac+1 !decreased from e-1 to e-3 - sph12/04
END IF

IF (nvskip0 .EQ. 0) nvskip0 = MAX(1, nvacskip)

IVAC0: IF (ivac .GE. 0) THEN
print *, "compute Nestor contribution"
!SPH OFF: 6.20.17
! IF INITIALLY ON, TURN OFF rcon0, zcon0 SLOWLY
print *, "reduce (r,z)con"
IF (lactive) THEN
IF (ictrl_prec2d .EQ. 2) THEN
prcon0(:,nsmin:nsmax) = 0; pzcon0(:,nsmin:nsmax) = 0
Expand All @@ -245,7 +255,10 @@ SUBROUTINE funct3d_par (lscreen, ier_flag)
ENDIF
CALL second0 (tvacon)
ivacskip = MOD(iter2-iter1,nvacskip)
IF (ivac .LE. 2) ivacskip = 0
IF (ivac .LE. 2) THEN
print *, "force full Nestor computation"
ivacskip = 0
END IF

! EXTEND NVACSKIP AS EQUILIBRIUM CONVERGES
IF (ivacskip .EQ. 0) THEN
Expand Down Expand Up @@ -348,7 +361,9 @@ SUBROUTINE funct3d_par (lscreen, ier_flag)
! RESET FIRST TIME FOR SOFT START
!
IF (ivac .EQ. 1) THEN
irst = 2; delt0 = delt
print *, "first Nestor call - force restart via BAD_JACOBIAN logic"
irst = 2
delt0 = delt
CALL restart_iter(delt0)
irst = 1
END IF
Expand All @@ -365,6 +380,7 @@ SUBROUTINE funct3d_par (lscreen, ier_flag)
presf_ns = (pmass(1._dp)/presf_ns) * pres(ns)
END IF

print *, "update rbsq"
DO l = 1, nznt
bsqsav(l,3) = 1.5_dp*pbzmn_o(l,ns)
& - 0.5_dp*pbzmn_o(l,ns-1)
Expand Down
4 changes: 4 additions & 0 deletions Sources/TimeStep/evolve.f
Original file line number Diff line number Diff line change
Expand Up @@ -146,6 +146,7 @@ SUBROUTINE evolve(time_step, ier_flag, liter_flag, lscreen)
! COMPUTE ABSOLUTE STOPPING CRITERION
IF (iter2.EQ.1 .and. irst.EQ.2) THEN
ier_flag = bad_jacobian_flag
print *, "absolute stop in Evolve"
RETURN
! JDH 2012-04-24. Revise this absolute stopping criterion, so that if v3fit
! is running, then have to iterate at least 2 * nvacskip steps
Expand All @@ -157,6 +158,7 @@ SUBROUTINE evolve(time_step, ier_flag, liter_flag, lscreen)
& fsql .le. ftolv) THEN
liter_flag = .false.
ier_flag = successful_term_flag
print *, "absolute stop in Evolve"
RETURN
ENDIF

Expand Down Expand Up @@ -315,6 +317,8 @@ SUBROUTINE TimeStepControl(ier_flag, PARVMEC)
! need to increment this here in order to not overwrite files
num_eqsolve_retries = num_eqsolve_retries + 1

print *, "try second funct3d call"

IF (PARVMEC) THEN
CALL funct3d_par(.FALSE., ier_flag)
ELSE
Expand Down

0 comments on commit d93018b

Please sign in to comment.