-
Notifications
You must be signed in to change notification settings - Fork 1
/
Copy pathvariablesND.f90
297 lines (258 loc) · 11 KB
/
variablesND.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
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
!------------------------------------------------------------------------------!
! NDSPMHD: A Smoothed Particle (Magneto)Hydrodynamics code for (astrophysical) !
! fluid dynamics simulations in 1, 2 and 3 spatial dimensions. !
! !
! (c) 2002-2015 Daniel Price !
! !
! http://users.monash.edu.au/~dprice/ndspmhd !
! daniel.price@monash.edu -or- dprice@cantab.net (forwards to current address) !
! !
! NDSPMHD comes with ABSOLUTELY NO WARRANTY. !
! This is free software; and you are welcome to redistribute !
! it under the terms of the GNU General Public License !
! (see LICENSE file for details) and the provision that !
! this notice remains intact. If you modify this file, please !
! note section 2a) of the GPLv2 states that: !
! !
! a) You must cause the modified files to carry prominent notices !
! stating that you changed the files and the date of any change. !
! !
! ChangeLog: !
!------------------------------------------------------------------------------!
!-------------------------------------------------------------------
! contains all the global variables used throughout the program
! sorted into modules (alphabetical order)
!-------------------------------------------------------------------
!-------------------------------------------------------------------
! quantities related to the artificial viscosity
! note alpha and alphain are regarded as particle properties (in module part)
! similarly the derivative of alpha is in module rates
!-------------------------------------------------------------------
module artvi
implicit none
real :: beta,avfact,avdecayconst
real :: alphamin,alphaumin,alphabmin
end module artvi
!-------------------------------------------------------------------
! boundary related quantities (boundary positions, array storing the
! real particle which is mirrored by the ghost)
!-------------------------------------------------------------------
module bound
use dimen_mhd
implicit none
integer, dimension(:), allocatable :: ireal
real, dimension(ndim) :: xmin, xmax
real :: hhmax,pext
end module bound
!-------------------------------------------------------------------
! debugging quantities
!-------------------------------------------------------------------
module debug
implicit none
integer :: itemp ! to print debugging info for a specific particle
logical :: trace
character(len=6) :: idebug
end module
!-------------------------------------------------------------------
! curl and divergence of the magnetic field
!-------------------------------------------------------------------
module derivB
implicit none
real, dimension(:), allocatable :: divB
real, dimension(:,:), allocatable :: curlB
real, dimension(:,:,:), allocatable :: gradB
end module
!-------------------------------------------------------------------
! Lorentz force
!-------------------------------------------------------------------
module fmagarray
implicit none
real, dimension(:,:), allocatable :: fmag
end module
!-------------------------------------------------------------------
! correction terms when using a spatially variable smoothing length
!-------------------------------------------------------------------
module hterms
implicit none
integer :: itsdensity
real, dimension(:), allocatable :: gradh,gradhn,gradsoft,gradgradh,zeta
real :: rhomin,h_min
end module hterms
!-------------------------------------------------------------------
! correction terms to make linear functions exact
!-------------------------------------------------------------------
module matrixcorr
use dimen_mhd, only:ndim
implicit none
integer, parameter :: ndxdx = ndim + (ndim*ndim - ndim)/2
integer, dimension(6), parameter :: idxdx = (/1,1,2,1,2,3/)
integer, dimension(6), parameter :: jdxdx = (/1,2,2,3,3,3/)
real, dimension(:,:), allocatable :: dxdx
end module matrixcorr
!-------------------------------------------------------------------
! quantities used for link-list neighbour finding
!-------------------------------------------------------------------
module linklist
use dimen_mhd
implicit none
integer, dimension(:), allocatable :: ll,ifirstincell,iamincell,numneigh
integer, dimension(ndim) :: ncellsx
integer :: ncells,ncellsloop
real :: dxcell
end module linklist
!-------------------------------------------------------------------
! logical unit numbers for input and output files
!-------------------------------------------------------------------
module loguns
implicit none
integer :: iprint,ievfile,idatfile,iread,ireadf
integer :: ifile
character(len=120) :: rootname ! name of the run
end module loguns
!-------------------------------------------------------------------
! program options
!-------------------------------------------------------------------
module options
use dimen_mhd
implicit none
integer :: iener,icty,iav,ikernav,idiffuse
integer :: idrag_nature,idrag_structure,ismooth
integer :: iprterm,idumpghost,ihvar,idust
integer :: imhd,imagforce,idivbzero ! (mhd options)
integer :: iexternal_force,ixsph,isplitpart
integer :: igravity,ikernel,ikernelalt,iresist
integer :: maxdensits,iuse_exact_derivs,nsteps_remap
integer :: ivisc,ibiascorrection,iambipolar,icompute_d2v
integer :: iquantum,idustevol,islope_limiter
integer, dimension(ndim) :: ibound
integer, dimension(3) :: iavlim
real :: damp,dampz,dampr,psidecayfact,tolh,hsoft,etamhd,rhocrit
real :: Kdrag,k_iso,k_par
real :: shearvisc,bulkvisc
real :: gamma_ambipolar,rho_ion
character(len=12) :: geom
logical :: usenumdens,onef_dust,use_smoothed_rhodust
end module
!-------------------------------------------------------------------
! basic particle properties
!-------------------------------------------------------------------
module part
use dimen_mhd
implicit none
integer :: npart,nbpts,ntotal
integer, parameter :: itypegas = 0
integer, parameter :: itypebnd = 1
integer, parameter :: itypedust = 2
integer, parameter :: itypegas1 = 3
integer, parameter :: itypegas2 = 4
integer, parameter :: itypebnd2 = 11
integer, parameter :: itypebnddust = 12
integer, parameter :: ndust = 1 ! number of dust species
integer, dimension(:), allocatable :: itype
real, dimension(:), allocatable :: pmass,sqrtg
real, dimension(:,:), allocatable :: x
real, dimension(:), allocatable :: dens,rho,pr,uu,en,hh,psi,spsound,rhoalt
real, dimension(:,:), allocatable :: vel,pmom,sourceterms,alpha
real, dimension(:,:), allocatable :: Bfield, Bevol, x0
real, dimension(:), allocatable :: rho0
real, dimension(ndimB) :: Bconst
real, dimension(:,:), allocatable :: deltav
real, dimension(:,:), allocatable :: dustfrac,dustevol,rhodust
real, dimension(:), allocatable :: rhogas
real, dimension(:,:), allocatable :: del2v,graddivv
real, dimension(:,:,:), allocatable :: P_Q
end module part
!-------------------------------------------------------------------
! particle properties at the beginning of the time step
!-------------------------------------------------------------------
module part_in
implicit none
real, dimension(:), allocatable :: rhoin,prin,hhin,enin,psiin
real, dimension(:,:), allocatable :: xin,velin,pmomin,alphain
real, dimension(:,:), allocatable :: Bevolin
real, dimension(:,:), allocatable :: deltavin
real, dimension(:,:), allocatable :: dustevolin
end module
!-------------------------------------------------------------------
! rates of change of particle properties (force, derivatives)
!-------------------------------------------------------------------
module rates
implicit none
real, dimension(:), allocatable :: drhodt,dudt,dendt,dhdt,dpsidt,poten
real, dimension(:,:), allocatable :: force,dBevoldt,daldt,gradpsi
real, dimension(:,:), allocatable :: ddeltavdt
real, dimension(:,:), allocatable :: ddustevoldt
real :: potengrav
end module rates
!-------------------------------------------------------------------
! rates of change at the beginning of the time step
!-------------------------------------------------------------------
!MODULE rates_in ! only needed if using leapfrog
! IMPLICIT NONE
! real, DIMENSION(:), ALLOCATABLE :: drhodtin,dudtin,dendtin,daldtin
! real, DIMENSION(:,:), ALLOCATABLE :: forcein,dBfielddtin
!END MODULE rates_in
!-------------------------------------------------------------------
! initial particle separation, initial smoothing length (in units of psep)
!-------------------------------------------------------------------
module setup_params
use dimen_mhd
use options, only:geom
implicit none
character(len=12) :: geomsetup
real, parameter :: pi = 3.1415926536
!
!--parameters for 2D-MRI simulations
!
real, parameter :: Rcentre = 1.
real, parameter :: Omega2 = 1./Rcentre**3
real, parameter :: Omega0 = Rcentre**(-1.5)
!--for a Keplerian rotation, domegadr = -dlnOmega/dlnr = q = -2A/Omega0 = 1.5
real, parameter :: domegadr = 1.5 !--1.5
real :: psep,hfact, R_grav,xlayer,Alayercs,dwidthlayer
real, parameter :: omegafixed = 1.0
logical :: have_setup_psi = .false. ! can be changed
end module setup_params
!-------------------------------------------------------------------
! time stepping related quantities
!-------------------------------------------------------------------
module timestep
implicit none
!
! (max tsteps, number of steps before output, current number of steps,
! number of steps before using a direct summation)
!
integer :: nmax,nout,nsteps,ndirect,nsubsteps_divB,iseedMC
!
! (max time, time before output, dt)
!
real :: tmax,tout,dt,dt0,time,vsig2max,dtscale
!
! (time step criterion from forces, courant condition)
!
real :: dtforce, dtcourant, C_force, C_cour, C_rho, dtrho
real :: dtav, dtdrag, dtvisc
logical, parameter :: dtfixed = .false.
end module timestep
!-------------------------------------------------------------------
! version number
!-------------------------------------------------------------------
module versn
implicit none
character(len=30) :: version
end module versn
!-------------------------------------------------------------------
! xsph factor
!-------------------------------------------------------------------
module xsph
implicit none
real, dimension(:,:), allocatable :: xsphterm
real :: xsphfac
end module xsph
!-------------------------------------------------------------------
! etavz factor
!-------------------------------------------------------------------
module streaming
implicit none
real, parameter :: eta=0.005
end module streaming