VMEC 8.52
3D Equilibrium solver with nested flux surfaces.
Loading...
Searching...
No Matches
printout.f90
Go to the documentation of this file.
1
3
9SUBROUTINE printout(i0, delt0, w0)
10 USE vmec_main
11 USE realspace
12 USE xstuff
13 use vmec_params, only: ntmax
14
15 use dbgout
16
17 IMPLICIT NONE
18
19 INTEGER :: i0
20 REAL(rprec) :: delt0, w0
21
22! #ifndef _HBANGLE
23 CHARACTER(LEN=*), PARAMETER :: iter_line = " ITER FSQR FSQZ CONR CONZ MHDR MHDZ FSQL "
24 CHARACTER(LEN=*), PARAMETER :: fsq_line = " fsqr fsqz conr conz mhdr mhdz fsql DELT "
25 CHARACTER(LEN=*), PARAMETER :: iter_lines = iter_line
26 CHARACTER(LEN=*), PARAMETER :: fsq_lines = fsq_line
27 CHARACTER(LEN=*), PARAMETER :: raxis_line = "RAX(v=0) "
28! #end /* ndef _HBANGLE */
29
30 CHARACTER(LEN=*), PARAMETER :: delt_line = " DELT "
31 CHARACTER(LEN=*), PARAMETER :: zaxis_line = " ZAX(v=0) "
32
33 REAL(rprec) :: betav, w, avm, den
34 CHARACTER(len=LEN(iter_line) + LEN(fsq_line) + LEN(raxis_line) + LEN(zaxis_line)) :: print_line
35 logical :: dbgout_printout
36
37 betav = wp/wb
38 w = w0*twopi*twopi
39
40 den = zero ! TODO: why? will be set of sum(vp(2:ns)) below anyway...
41 specw(1) = one
42 gc = xstore ! TODO: why compute spectral width from backup and not current gc (== physical xc) --> <M> includes scalxc ???
43
44 dbgout_printout = open_dbg_context("printout", num_eqsolve_retries)
45 if (dbgout_printout) then
46 ! dump gc before it gets modified by spectrum() below
47 call add_real_5d("gc", 3, ntmax, ns, ntor1, mpol, gc, order=(/ 3, 4, 5, 2, 1 /) )
48 end if ! dbgout_printout
49
50 CALL spectrum (gc(:irzloff), gc(1+irzloff:2*irzloff))
51 den = sum(vp(2:ns))
52 avm = dot_product(vp(2:ns), specw(2:ns)+specw(1:ns-1))
53 avm = 0.5_dp*avm/den ! volume-averaged spectral width (_av_erage _M_)
54
55 delbsq = 0.0_dp ! default output in case of fixed-boundary run
56 IF (ivac .ge. 1 .and. iter2.gt.1) then
57 delbsq = sum( dbsq(:nznt)*wint(2:nrzt:ns) ) / sum( bsqsav(:nznt,3)*wint(2:nrzt:ns) )
58 end if
59
60 if (dbgout_printout) then
61 call add_real("betav", betav)
62 call add_real("avm", avm)
63 call add_real("delbsq", delbsq)
64
65 call add_real_1d("specw", ns, specw)
66
67 call close_dbg_out()
68 end if ! printout
69
70 IF (i0.eq.1 .and. lfreeb) THEN
71 print_line = iter_lines // " " // raxis_line
72 IF (lasym) print_line = trim(print_line) // " " // zaxis_line
73 print 20, trim(print_line)//delt_line
74 print_line = iter_line // fsq_line // raxis_line
75 IF (lasym) print_line = trim(print_line) // " " // zaxis_line
76 WRITE (nthreed, 16) trim(print_line)
77 ELSE IF (i0.eq.1 .and. .not.lfreeb) THEN
78 print_line = raxis_line
79 IF (lasym) print_line = raxis_line // zaxis_line
80 print 30, iter_lines, trim(print_line)//delt_line
81 print_line = iter_line // fsq_line // raxis_line // " "
82 IF (lasym) then
83 print_line = iter_line // fsq_line // raxis_line // zaxis_line
84 end if
85 WRITE (nthreed, 25) trim(print_line)
86 ENDIF
8716 FORMAT(/,a,6x,'WMHD BETA PHIEDGE DEL-BSQ FEDGE',/)
8820 FORMAT(/,a,6x,'WMHD DEL-BSQ',/)
8925 FORMAT(/,a,6x,'WMHD BETA <M> ',/)
9030 FORMAT(/,a,1x,a,5x,'WMHD',/)
91
92 IF (.not. lasym) THEN
93 IF (.not.lfreeb) THEN
94 print 45, i0, fsqr, fsqz, fsqr_con, fsqz_con, fsqr_mhd, fsqz_mhd, &
95 fsql, r00, delt0, w
96 WRITE (nthreed, 40) i0, fsqr, fsqz, fsqr_con, fsqz_con, fsqr_mhd, fsqz_mhd, &
98 delt0, r00, w, betav, avm
99 RETURN
100 ENDIF
101 print 50, i0, fsqr, fsqz, fsqr_con, fsqz_con, fsqr_mhd, fsqz_mhd, &
102 fsql, r00, delt0, w, delbsq
103 WRITE (nthreed, 42) i0, fsqr, fsqz, fsqr_con, fsqz_con, fsqr_mhd, fsqz_mhd, &
105 fsql1, delt0, r00, w, betav, abs(phiedge), delbsq, fedge
106
107 ELSE ! (.not. lasym)
108 IF (.not.lfreeb) THEN
109 print 65, i0, fsqr, fsqz, fsqr_con, fsqz_con, fsqr_mhd, fsqz_mhd, &
110 fsql, r00, z00, delt0, w
111 WRITE (nthreed, 60) i0, fsqr, fsqz, fsqr_con, fsqz_con, fsqr_mhd, fsqz_mhd, &
113 fsql1, delt0, r00, z00, w, betav, avm
114 RETURN
115 ENDIF
116 print 70, i0, fsqr, fsqz, fsqr_con, fsqz_con, fsqr_mhd, fsqz_mhd, &
117 fsql, r00, z00, delt0, w, delbsq
118 WRITE (nthreed, 60) i0, fsqr, fsqz, fsqr_con, fsqz_con, fsqr_mhd, fsqz_mhd, &
120 fsql1, delt0, r00, z00, w, betav, abs(phiedge), delbsq, fedge
121 END IF
122
12340 FORMAT(i6,1x,1p,15e10.2,e11.3,e12.4,e11.3,0p,f7.3,1p,2e9.2)
12442 FORMAT(i5,1p,15e10.2,e11.3,e12.4,2e11.3,0p,f7.3,1p,e9.2)
12545 FORMAT(i5,1p,7e10.2,e11.3,e10.2,e12.4)
12650 FORMAT(i5,1p,7e10.2,e11.3,e10.2,e12.4,e11.3)
12760 FORMAT(i6,1x,1p,15e10.2,2e11.3,e12.4,e11.3,0p,f7.3,1p,2e9.2)
12865 FORMAT(i5,1p,7e10.2,2e11.3,e10.2,e12.4)
12970 FORMAT(i5,1p,7e10.2,2e11.3,e10.2,e12.4,e11.3)
130
131END SUBROUTINE printout
logical function open_dbg_context(context_name, repetition, id)
check if any output is desired for the current iteration check if the given context should be openend...
Definition dbgout.f90:17
real(rprec), dimension(:), allocatable wint
two-dimensional array for normalizing angle integrations
Definition realspace.f90:34
integer irzloff
offset in xc array between R,Z,L components
real(rprec), dimension(:), allocatable vp
radial derivative of enclosed volume
Definition vmec_main.f90:56
real(rprec) fsqr_con
real(rprec) fsqz1
real(rprec) fsql
Definition vmec_main.f90:96
real(rprec) fsqr1_con
real(rprec) wp
kinetic/thermal energy (from pressure)
real(rprec) fsqr
Definition vmec_main.f90:94
real(rprec) fsqz
Definition vmec_main.f90:95
real(rprec), dimension(:), allocatable dbsq
real(rprec) delbsq
real(rprec) fsqz1_con
real(rprec) z00
Definition vmec_main.f90:91
real(rprec) fsqr1_mhd
real(rprec) fsqz_mhd
real(rprec) fsqr_mhd
real(rprec) r00
Definition vmec_main.f90:89
integer ivac
counts number of free-boundary iterations
real(rprec), dimension(:), allocatable specw
spectral width (diagnostic)
Definition vmec_main.f90:46
real(rprec), dimension(:,:), allocatable bsqsav
Definition vmec_main.f90:73
real(rprec) fsqr1
Definition vmec_main.f90:99
real(rprec) wb
magnetic energy: volume integral over B^2/2
integer num_eqsolve_retries
real(rprec) fedge
real(rprec) fsql1
real(rprec) fsqz1_mhd
integer iter2
total number of iterations
real(rprec) fsqz_con
integer ntmax
number of contributing Fourier basis function (can be 1, 2 or 4); assigned in read_indata()
real(rprec), dimension(:), allocatable gc
stacked array of R, Z, Lambda Spectral force coefficients (see above for stack order)
Definition xstuff.f90:37
real(rprec), dimension(:), allocatable xstore
backup copy of last-known-good xc
Definition xstuff.f90:48
subroutine printout(i0, delt0, w0)
Print iteration progress to screen and threed1 output file.
Definition printout.f90:10
subroutine spectrum(rmn, zmn)
Compute the spectral width of the surface geometry Fourier coefficients.
Definition spectrum.f90:9