-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathpreload_for_SYNCH.f90
69 lines (68 loc) · 2.29 KB
/
preload_for_SYNCH.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
subroutine preload_for_SYNCH
!
use magdata_in_symfluxcoor_mod, only: btor, rbig
implicit none
!
integer :: nstep,nsurfmax,nlabel,ntheta,i
!
double precision :: rmn,rmx,zmn,zmx,raxis,zaxis
double precision, dimension(:), allocatable :: rbeg,rsmall,qsaf,psisurf,phitor,circumf
double precision, dimension(:,:), allocatable :: R_st,Z_st,bmod_st,sqgnorm_st
!
open(1,file='preload_for_SYNCH.inp')
read (1,*) nstep !number of integration steps
read (1,*) nlabel !grid size over radial variabl
read (1,*) ntheta !grid size over poloidal angle
read (1,*) nsurfmax !number of starting points between the
!magnetic axis and right box boundary
!when searching for the separatrix
close(1)
!
allocate(rbeg(nlabel),rsmall(nlabel),qsaf(nlabel),psisurf(nlabel),phitor(nlabel),circumf(nlabel))
allocate(R_st(nlabel,ntheta),Z_st(nlabel,ntheta),bmod_st(nlabel,ntheta),sqgnorm_st(nlabel,ntheta))
!
call field_line_integration_for_SYNCH(nstep,nsurfmax,nlabel,ntheta, &
rmn,rmx,zmn,zmx,raxis,zaxis, &
rbeg,rsmall,qsaf,psisurf,phitor, &
circumf,R_st,Z_st,bmod_st,sqgnorm_st)
!
open(1,file='btor_rbig.dat')
write (1,*) btor,rbig
close(1)
open(1,form='formatted',file='box_size_axis.dat')
write (1,*) rmn,rmx, '<= rmn, rmx (cm)'
write (1,*) zmn,zmx, '<= zmn, zmx (cm)'
write (1,*) raxis,zaxis, '<= raxis, zaxis (cm)'
close(1)
!
open(1,form='formatted',file='flux_functions.dat')
write (1,*) '# R_beg, r, q, psi_pol, psi_tor, circumf'
do i=1,nlabel
write (1,*) rbeg(i),rsmall(i),qsaf(i),psisurf(i),phitor(i),circumf(i)
enddo
close(1)
!
open(1,form='formatted',file='twodim_functions.dat')
write (1,*) nlabel, ntheta, '<= nlabel, ntheta'
write (1,*) 'R(label,theta)'
do i=1,nlabel
write (1,*) R_st(i,:)
enddo
write (1,*) 'Z(label,theta)'
do i=1,nlabel
write (1,*) Z_st(i,:)
enddo
write (1,*) 'B(label,theta)'
do i=1,nlabel
write (1,*) bmod_st(i,:)
enddo
write (1,*) 'sqrtg_norm(label,theta)'
do i=1,nlabel
write (1,*) sqgnorm_st(i,:)
enddo
close(1)
!
deallocate(rbeg,rsmall,qsaf,psisurf,phitor,circumf)
deallocate(R_st,Z_st,bmod_st,sqgnorm_st)
!
end subroutine preload_for_SYNCH