Skip to content

Commit

Permalink
dump gc before being modified in spectrum()
Browse files Browse the repository at this point in the history
  • Loading branch information
jons-pf committed Oct 10, 2023
1 parent f416327 commit a49c7cd
Show file tree
Hide file tree
Showing 3 changed files with 11 additions and 3 deletions.
1 change: 1 addition & 0 deletions src/eqsolve.f90
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@ SUBROUTINE eqsolve(ier_flag)
! RESTART FROM INITIAL PROFILE, BUT WITH A SMALLER TIME-STEP
IF (first .EQ. 2) THEN
xc = 0.0_dp

CALL profil3d (xc(1), xc(1+irzloff), lreset_internal)

first = 1 ! tells restart_iter to store current xc in xstore
Expand Down
11 changes: 9 additions & 2 deletions src/printout.f90
Original file line number Diff line number Diff line change
Expand Up @@ -32,13 +32,21 @@ SUBROUTINE printout(i0, delt0, w0)

REAL(rprec) :: betav, w, avm, den
CHARACTER(len=LEN(iter_line) + LEN(fsq_line) + LEN(raxis_line) + LEN(zaxis_line)) :: print_line
logical :: dbgout_printout

betav = wp/wb
w = w0*twopi*twopi

den = zero ! TODO: why? will be set of sum(vp(2:ns)) below anyway...
specw(1) = one
gc = xstore ! TODO: why compute spectral width from backup and not current gc (== physical xc) --> <M> includes scalxc ???

dbgout_printout = open_dbg_context("printout", num_eqsolve_retries)
if (dbgout_printout) then
! dump gc before it gets modified by spectrum() below
call add_real_5d("gc", 3, ntmax, ns, ntor1, mpol, gc, order=(/ 3, 4, 5, 2, 1 /) )
end if ! dbgout_printout

CALL spectrum (gc(:irzloff), gc(1+irzloff:2*irzloff))
den = SUM(vp(2:ns))
avm = DOT_PRODUCT(vp(2:ns), specw(2:ns)+specw(1:ns-1))
Expand All @@ -49,12 +57,11 @@ SUBROUTINE printout(i0, delt0, w0)
delbsq = SUM( dbsq(:nznt)*wint(2:nrzt:ns) ) / SUM( bsqsav(:nznt,3)*wint(2:nrzt:ns) )
end if

if (open_dbg_context("printout")) then
if (dbgout_printout) then
call add_real("betav", betav)
call add_real("avm", avm)
call add_real("delbsq", delbsq)

call add_real_5d("gc", 3, ntmax, ns, ntor1, mpol, gc, order=(/ 3, 4, 5, 2, 1 /) )
call add_real_1d("specw", ns, specw)

call close_dbg_out()
Expand Down
2 changes: 1 addition & 1 deletion src/restart_iter.f90
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ SUBROUTINE restart_iter(time_step)
! if (first .ne. 1) then
! print *, "bad jacobian --> restart_iter (first = ", first, ")"
! end if

SELECT CASE (first)
case(2)
! restore previous good state
Expand Down

0 comments on commit a49c7cd

Please sign in to comment.