V3FIT
initialize_radial.f
1  SUBROUTINE initialize_radial(nsval, ns_old, delt0,
2  1 lscreen, reset_file_name)
3  USE vmec_main
4  USE vmec_params, ONLY: ntmax
5  USE realspace
6  USE xstuff
7 #ifdef _HBANGLE
8  USE angle_constraints, ONLY: getrz, store_init_array
9 #endif
10  USE parallel_include_module
11  IMPLICIT NONE
12 C-----------------------------------------------
13 C D u m m y A r g u m e n t s
14 C-----------------------------------------------
15  INTEGER, INTENT(IN) :: nsval
16  INTEGER, INTENT(INOUT) :: ns_old
17  CHARACTER(LEN=*), OPTIONAL :: reset_file_name
18  REAL(dp), INTENT(OUT) :: delt0
19  LOGICAL, INTENT(IN) :: lscreen
20 C-----------------------------------------------
21 C L o c a l V a r i a b l e s
22 C-----------------------------------------------
23  INTEGER :: neqs_old = 0
24  LOGICAL :: lreset_internal, linterp
25  INTEGER :: nsmin, nsmax, i, j, k, l, lk
26 C-----------------------------------------------
27 !
28 ! Allocates memory for radial arrays and initializes radial profiles
29 ! Loads data (if available) from a reset file
30 !
31 C-----------------------------------------------
32 !
33 ! INDEX OF LOCAL VARIABLES
34 !
35 ! hs radial mesh size increment
36 ! irzloff offset in xc array between R,Z,L components
37 ! neqs total number of equations to evolve (size of xc)
38 C-----------------------------------------------
39 ! Set timestep control parameters
40  fsq = one
41  iter2 = 1
42  iter1 = iter2
43  ijacob = 0
44  irst = 1
45  res0 = -1
46 !
47 ! INITIALIZE MESH-DEPENDENT SCALARS
48 !
49  ns = nsval
50  ns1 = ns - 1
51  delt0 = delt
52  hs = one/ns1
53  ohs = one/hs
54  mns = ns*mnsize
55  irzloff = ntmax*mns
56  nrzt = nznt*ns
57  neqs = 3*irzloff
58 
59 
60  IF (grank .EQ. 0) THEN
61  WRITE (nthreed, 1000) ns, mnmax, ftolv, niter
62  IF (lscreen) THEN
63  print 1000, ns, mnmax, ftolv, niter
64  END IF
65  IF (lactive) THEN
66  IF (lfreeb) THEN
67  WRITE(nthreed,1002) nranks, vnranks
68  IF (lscreen) print 1002, nranks, vnranks
69  ELSE
70  WRITE (nthreed, 1001) nranks
71  IF (lscreen) print 1001, nranks
72  END IF
73  END IF
74  END IF
75 
76 !
77 ! ALLOCATE NS-DEPENDENT ARRAYS
78 !
79  lreset_internal = .true.
80  linterp = (ns_old .LT. ns .AND. ns_old .NE. 0)
81  IF (ns_old .EQ. ns) RETURN
82  CALL allocate_ns(linterp, neqs_old)
83 !
84 ! SAVE THIS FOR INTERPOLATION
85 !
86  IF (neqs_old.gt.0 .and. linterp) THEN
87 #ifdef _HBANGLE
88  ns = ns_old
89  CALL getrz(xstore)
90  ns = ns1 + 1
91 #endif
92  IF (parvmec) THEN
93 #if defined(MPI_OPT)
94  pgc(1:neqs_old) = pscalxc(1:neqs_old)*pxstore(1:neqs_old)
95  IF (lfreeb) THEN
96  CALL mpi_bcast(rbsq, SIZE(rbsq), mpi_real8,
97  & 0, ns_comm, mpi_err)
98  END IF
99 #endif
100  ELSE
101  gc(1:neqs_old) = scalxc(1:neqs_old)*xstore(1:neqs_old)
102  END IF
103  END IF
104 
105 !
106 ! COMPUTE INITIAL R, Z AND MAGNETIC FLUX PROFILES
107 !
108 
109  IF (parvmec) THEN
110  CALL profil1d_par(pxc, pxcdot, lreset_internal)
111  ELSE
112  CALL profil1d(xc, xcdot, lreset_internal)
113  END IF
114  IF (PRESENT(reset_file_name)) THEN
115  IF (len_trim(reset_file_name) .ne. 0) THEN
116  CALL load_xc_from_wout(xc(1), xc(1+irzloff),
117  & xc(1+2*irzloff), lreset_internal,
118  & ntor, mpol1, ns, reset_file_name)
119  IF (parvmec) THEN
120  CALL serial2parallel4x(xc,pxc)
121  END IF
122  END IF
123  END IF
124 
125  IF (parvmec) THEN
126  CALL profil3d_par(pxc(1), pxc(1+irzloff), lreset_internal,
127  & linterp)
128  ELSE
129  CALL profil3d(xc(1), xc(1+irzloff), lreset_internal, linterp)
130  END IF
131 !
132 ! INTERPOLATE FROM COARSE (ns_old) TO NEXT FINER (ns) RADIAL GRID
133 !
134  IF (linterp) THEN
135  IF(parvmec) THEN
136  CALL interp_par(pxc, pgc, pscalxc, ns, ns_old)
137  ELSE
138  CALL interp(xc, gc, scalxc, ns, ns_old)
139  END IF
140 #ifdef _HBANGLE
141  CALL store_init_array(xc)
142 #endif
143  END IF
144 
145 !SPH 012417: move this AFTER interpolation call
146  irst = 1
147  CALL restart_iter(delt)
148 
149  ns_old = ns
150  neqs_old = neqs
151 
152 1000 FORMAT(/' NS = ',i4,' NO. FOURIER MODES = ',i4,' FTOLV = ',
153  & 1p,e10.3,' NITER = ',i6)
154 1001 FORMAT(' PROCESSOR COUNT - RADIAL: ',i4)
155 1002 FORMAT(' PROCESSOR COUNT - RADIAL: ',i4,' VACUUM: ',i4)
156 
157  END SUBROUTINE initialize_radial