geometry_cylindrical.f90
Go to the documentation of this file.
1!#############################################################################
2!# #
3!# fosite - 3D hydrodynamical simulation program #
4!# module: geometry_cylindrical.f90 #
5!# #
6!# Copyright (C) 2007 Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
7!# Jubin Lirawi <jlirawi@astrophysik.uni-kiel.de> #
8!# #
9!# This program is free software; you can redistribute it and/or modify #
10!# it under the terms of the GNU General Public License as published by #
11!# the Free Software Foundation; either version 2 of the License, or (at #
12!# your option) any later version. #
13!# #
14!# This program is distributed in the hope that it will be useful, but #
15!# WITHOUT ANY WARRANTY; without even the implied warranty of #
16!# MERCHANTABILITY OR FITNESS FOR A PARTICULAR PURPOSE, GOOD TITLE or #
17!# NON INFRINGEMENT. See the GNU General Public License for more #
18!# details. #
19!# #
20!# You should have received a copy of the GNU General Public License #
21!# along with this program; if not, write to the Free Software #
22!# Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. #
23!# #
24!#############################################################################
25
26!----------------------------------------------------------------------------!
35!----------------------------------------------------------------------------!
38 USE common_dict
39 IMPLICIT NONE
40 !--------------------------------------------------------------------------!
42 CONTAINS
44 PROCEDURE :: scalefactors_1
45 PROCEDURE :: scalefactors_2
46 PROCEDURE :: scalefactors_3
47 PROCEDURE :: scalefactors_4
48 PROCEDURE :: radius_1
49 PROCEDURE :: radius_2
50 PROCEDURE :: radius_3
51 PROCEDURE :: radius_4
52 PROCEDURE :: positionvector_1
53 PROCEDURE :: positionvector_2
54 PROCEDURE :: positionvector_3
55 PROCEDURE :: positionvector_4
72 PROCEDURE :: finalize
73 END TYPE
74 PRIVATE
75 CHARACTER(LEN=32), PARAMETER :: geometry_name = "cylindrical"
76 !--------------------------------------------------------------------------!
77 PUBLIC :: geometry_cylindrical
78 !--------------------------------------------------------------------------!
79
80CONTAINS
81
82 SUBROUTINE initgeometry_cylindrical(this,config)
83 IMPLICIT NONE
84 !------------------------------------------------------------------------!
85 CLASS(geometry_cylindrical), INTENT(INOUT) :: this
86 TYPE(dict_typ), POINTER :: config
87 !------------------------------------------------------------------------!
88 CALL this%InitGeometry(cylindrical,geometry_name,config)
89 CALL this%SetAzimuthIndex(2)
90 END SUBROUTINE initgeometry_cylindrical
91
92 PURE SUBROUTINE scalefactors_1(this,coords,hx,hy,hz)
93 IMPLICIT NONE
94 !------------------------------------------------------------------------!
95 CLASS(geometry_cylindrical), INTENT(IN) :: this
96 REAL, INTENT(IN), DIMENSION(:,:) :: coords
97 REAL, INTENT(OUT), DIMENSION(:) :: hx,hy,hz
98 !------------------------------------------------------------------------!
99 CALL scalefactors(coords(:,1),hx(:),hy(:),hz(:))
100 END SUBROUTINE scalefactors_1
101
102 PURE SUBROUTINE scalefactors_2(this,coords,hx,hy,hz)
103 IMPLICIT NONE
104 !------------------------------------------------------------------------!
105 CLASS(geometry_cylindrical), INTENT(IN) :: this
106 REAL, INTENT(IN), DIMENSION(:,:,:) :: coords
107 REAL, INTENT(OUT), DIMENSION(:,:) :: hx,hy,hz
108 !------------------------------------------------------------------------!
109 CALL scalefactors(coords(:,:,1),hx(:,:),hy(:,:),hz(:,:))
110 END SUBROUTINE scalefactors_2
111
112 PURE SUBROUTINE scalefactors_3(this,coords,hx,hy,hz)
113 IMPLICIT NONE
114 !------------------------------------------------------------------------!
115 CLASS(geometry_cylindrical), INTENT(IN) :: this
116 REAL, INTENT(IN), DIMENSION(:,:,:,:) :: coords
117 REAL, INTENT(OUT), DIMENSION(:,:,:) :: hx,hy,hz
118 !------------------------------------------------------------------------!
119 CALL scalefactors(coords(:,:,:,1),hx(:,:,:),hy(:,:,:),hz(:,:,:))
120 END SUBROUTINE scalefactors_3
121
122 PURE SUBROUTINE scalefactors_4(this,coords,hx,hy,hz)
123 IMPLICIT NONE
124 !------------------------------------------------------------------------!
125 CLASS(geometry_cylindrical), INTENT(IN) :: this
126 REAL, INTENT(IN), DIMENSION(:,:,:,:,:) :: coords
127 REAL, INTENT(OUT), DIMENSION(:,:,:,:) :: hx,hy,hz
128 !------------------------------------------------------------------------!
129 CALL scalefactors(coords(:,:,:,:,1),hx(:,:,:,:),hy(:,:,:,:),hz(:,:,:,:))
130 END SUBROUTINE scalefactors_4
131
132 PURE SUBROUTINE radius_1(this,coords,r)
133 IMPLICIT NONE
134 !------------------------------------------------------------------------!
135 CLASS(geometry_cylindrical), INTENT(IN) :: this
136 REAL, DIMENSION(:,:), INTENT(IN) :: coords
137 REAL, DIMENSION(:), INTENT(OUT) :: r
138 !------------------------------------------------------------------------!
139 r = radius(coords(:,1),coords(:,3))
140 END SUBROUTINE radius_1
141
142 PURE SUBROUTINE radius_2(this,coords,r)
143 IMPLICIT NONE
144 !------------------------------------------------------------------------!
145 CLASS(geometry_cylindrical), INTENT(IN) :: this
146 REAL, DIMENSION(:,:,:), INTENT(IN) :: coords
147 REAL, DIMENSION(:,:), INTENT(OUT) :: r
148 !------------------------------------------------------------------------!
149 r = radius(coords(:,:,1),coords(:,:,3))
150 END SUBROUTINE radius_2
151
152 PURE SUBROUTINE radius_3(this,coords,r)
153 IMPLICIT NONE
154 !------------------------------------------------------------------------!
155 CLASS(geometry_cylindrical), INTENT(IN) :: this
156 REAL, DIMENSION(:,:,:,:), INTENT(IN) :: coords
157 REAL, DIMENSION(:,:,:), INTENT(OUT) :: r
158 !------------------------------------------------------------------------!
159 r = radius(coords(:,:,:,1),coords(:,:,:,3))
160 END SUBROUTINE radius_3
161
162 PURE SUBROUTINE radius_4(this,coords,r)
163 IMPLICIT NONE
164 !------------------------------------------------------------------------!
165 CLASS(geometry_cylindrical), INTENT(IN) :: this
166 REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: coords
167 REAL, DIMENSION(:,:,:,:), INTENT(OUT) :: r
168 !------------------------------------------------------------------------!
169 r = radius(coords(:,:,:,:,1),coords(:,:,:,:,3))
170 END SUBROUTINE radius_4
171
172 PURE SUBROUTINE positionvector_1(this,coords,posvec)
173 IMPLICIT NONE
174 !------------------------------------------------------------------------!
175 CLASS(geometry_cylindrical), INTENT(IN) :: this
176 REAL, DIMENSION(:,:), INTENT(IN) :: coords
177 REAL, DIMENSION(:,:), INTENT(OUT) :: posvec
178 !------------------------------------------------------------------------!
179 CALL positionvector(coords(:,1),coords(:,3),posvec(:,1),posvec(:,2),posvec(:,3))
180 END SUBROUTINE positionvector_1
181
182 PURE SUBROUTINE positionvector_2(this,coords,posvec)
183 IMPLICIT NONE
184 !------------------------------------------------------------------------!
185 CLASS(geometry_cylindrical), INTENT(IN) :: this
186 REAL, DIMENSION(:,:,:), INTENT(IN) :: coords
187 REAL, DIMENSION(:,:,:), INTENT(OUT) :: posvec
188 !------------------------------------------------------------------------!
189 CALL positionvector(coords(:,:,1),coords(:,:,3),posvec(:,:,1), &
190 posvec(:,:,2),posvec(:,:,3))
191 END SUBROUTINE positionvector_2
192
193 PURE SUBROUTINE positionvector_3(this,coords,posvec)
194 IMPLICIT NONE
195 !------------------------------------------------------------------------!
196 CLASS(geometry_cylindrical), INTENT(IN) :: this
197 REAL, DIMENSION(:,:,:,:), INTENT(IN) :: coords
198 REAL, DIMENSION(:,:,:,:), INTENT(OUT) :: posvec
199 !------------------------------------------------------------------------!
200 CALL positionvector(coords(:,:,:,1),coords(:,:,:,3),posvec(:,:,:,1), &
201 posvec(:,:,:,2),posvec(:,:,:,3))
202 END SUBROUTINE positionvector_3
203
204 PURE SUBROUTINE positionvector_4(this,coords,posvec)
205 IMPLICIT NONE
206 !------------------------------------------------------------------------!
207 CLASS(geometry_cylindrical), INTENT(IN) :: this
208 REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: coords
209 REAL, DIMENSION(:,:,:,:,:), INTENT(OUT) :: posvec
210 !------------------------------------------------------------------------!
211 CALL positionvector(coords(:,:,:,:,1),coords(:,:,:,:,3),posvec(:,:,:,:,1), &
212 posvec(:,:,:,:,2),posvec(:,:,:,:,3))
213 END SUBROUTINE positionvector_4
214
215 PURE SUBROUTINE convert2cartesian_coords_1(this,curv,cart)
216 IMPLICIT NONE
217 !------------------------------------------------------------------------!
218 CLASS(geometry_cylindrical), INTENT(IN) :: this
219 REAL, DIMENSION(:,:), INTENT(IN) :: curv
220 REAL, DIMENSION(:,:), INTENT(OUT) :: cart
221 !------------------------------------------------------------------------!
222 CALL convert2cartesian_coords(curv(:,1),curv(:,2),curv(:,3), &
223 cart(:,1),cart(:,2),cart(:,3))
224 END SUBROUTINE convert2cartesian_coords_1
225
226 PURE SUBROUTINE convert2cartesian_coords_2(this,curv,cart)
227 IMPLICIT NONE
228 !------------------------------------------------------------------------!
229 CLASS(geometry_cylindrical), INTENT(IN) :: this
230 REAL, DIMENSION(:,:,:), INTENT(IN) :: curv
231 REAL, DIMENSION(:,:,:), INTENT(OUT) :: cart
232 !------------------------------------------------------------------------!
233 CALL convert2cartesian_coords(curv(:,:,1),curv(:,:,2),curv(:,:,3), &
234 cart(:,:,1),cart(:,:,2),cart(:,:,3))
235 END SUBROUTINE convert2cartesian_coords_2
236
237 PURE SUBROUTINE convert2cartesian_coords_3(this,curv,cart)
238 IMPLICIT NONE
239 !------------------------------------------------------------------------!
240 CLASS(geometry_cylindrical), INTENT(IN) :: this
241 REAL, DIMENSION(:,:,:,:), INTENT(IN) :: curv
242 REAL, DIMENSION(:,:,:,:), INTENT(OUT) :: cart
243 !------------------------------------------------------------------------!
244 CALL convert2cartesian_coords(curv(:,:,:,1),curv(:,:,:,2),curv(:,:,:,3), &
245 cart(:,:,:,1),cart(:,:,:,2),cart(:,:,:,3))
246 END SUBROUTINE convert2cartesian_coords_3
247
248 PURE SUBROUTINE convert2cartesian_coords_4(this,curv,cart)
249 IMPLICIT NONE
250 !------------------------------------------------------------------------!
251 CLASS(geometry_cylindrical), INTENT(IN) :: this
252 REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: curv
253 REAL, DIMENSION(:,:,:,:,:), INTENT(OUT) :: cart
254 !------------------------------------------------------------------------!
255 CALL convert2cartesian_coords(curv(:,:,:,:,1),curv(:,:,:,:,2),curv(:,:,:,:,3), &
256 cart(:,:,:,:,1),cart(:,:,:,:,2),cart(:,:,:,:,3))
257 END SUBROUTINE convert2cartesian_coords_4
258
259 PURE SUBROUTINE convert2curvilinear_coords_1(this,cart,curv)
260 IMPLICIT NONE
261 !------------------------------------------------------------------------!
262 CLASS(geometry_cylindrical), INTENT(IN) :: this
263 REAL, DIMENSION(:,:), INTENT(IN) :: cart
264 REAL, DIMENSION(:,:), INTENT(OUT) :: curv
265 !------------------------------------------------------------------------!
266 CALL convert2curvilinear_coords(cart(:,1),cart(:,2),cart(:,3), &
267 curv(:,1),curv(:,2),curv(:,3))
268 END SUBROUTINE convert2curvilinear_coords_1
269
270 PURE SUBROUTINE convert2curvilinear_coords_2(this,cart,curv)
271 IMPLICIT NONE
272 !------------------------------------------------------------------------!
273 CLASS(geometry_cylindrical), INTENT(IN) :: this
274 REAL, DIMENSION(:,:,:), INTENT(IN) :: cart
275 REAL, DIMENSION(:,:,:), INTENT(OUT) :: curv
276 !------------------------------------------------------------------------!
277 CALL convert2curvilinear_coords(cart(:,:,1),cart(:,:,2),cart(:,:,3), &
278 curv(:,:,1),curv(:,:,2),curv(:,:,3))
279 END SUBROUTINE convert2curvilinear_coords_2
280
281 PURE SUBROUTINE convert2curvilinear_coords_3(this,cart,curv)
282 IMPLICIT NONE
283 !------------------------------------------------------------------------!
284 CLASS(geometry_cylindrical), INTENT(IN) :: this
285 REAL, DIMENSION(:,:,:,:), INTENT(IN) :: cart
286 REAL, DIMENSION(:,:,:,:), INTENT(OUT) :: curv
287 !------------------------------------------------------------------------!
288 CALL convert2curvilinear_coords(cart(:,:,:,1),cart(:,:,:,2),cart(:,:,:,3), &
289 curv(:,:,:,1),curv(:,:,:,2),curv(:,:,:,3))
290 END SUBROUTINE convert2curvilinear_coords_3
291
292 PURE SUBROUTINE convert2curvilinear_coords_4(this,cart,curv)
293 IMPLICIT NONE
294 !------------------------------------------------------------------------!
295 CLASS(geometry_cylindrical), INTENT(IN) :: this
296 REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: cart
297 REAL, DIMENSION(:,:,:,:,:), INTENT(OUT) :: curv
298 !------------------------------------------------------------------------!
299 CALL convert2curvilinear_coords(cart(:,:,:,:,1),cart(:,:,:,:,2),cart(:,:,:,:,3), &
300 curv(:,:,:,:,1),curv(:,:,:,:,2),curv(:,:,:,:,3))
301 END SUBROUTINE convert2curvilinear_coords_4
302
303 PURE SUBROUTINE convert2cartesian_vectors_1(this,curv,v_curv,v_cart)
304 IMPLICIT NONE
305 !------------------------------------------------------------------------!
306 CLASS(geometry_cylindrical), INTENT(IN) :: this
307 REAL, DIMENSION(:,:), INTENT(IN) :: curv
308 REAL, DIMENSION(:,:), INTENT(IN) :: v_curv
309 REAL, DIMENSION(:,:), INTENT(OUT) :: v_cart
310 !------------------------------------------------------------------------!
311 CALL convert2cartesian_vectors(curv(:,1),curv(:,2),curv(:,3), &
312 v_curv(:,1),v_curv(:,2),v_curv(:,3), &
313 v_cart(:,1),v_cart(:,2),v_cart(:,3))
314 END SUBROUTINE convert2cartesian_vectors_1
315
316 PURE SUBROUTINE convert2cartesian_vectors_2(this,curv,v_curv,v_cart)
317 IMPLICIT NONE
318 !------------------------------------------------------------------------!
319 CLASS(geometry_cylindrical), INTENT(IN) :: this
320 REAL, DIMENSION(:,:,:), INTENT(IN) :: curv
321 REAL, DIMENSION(:,:,:), INTENT(IN) :: v_curv
322 REAL, DIMENSION(:,:,:), INTENT(OUT) :: v_cart
323 !------------------------------------------------------------------------!
324 CALL convert2cartesian_vectors(curv(:,:,1),curv(:,:,2),curv(:,:,3), &
325 v_curv(:,:,1),v_curv(:,:,2),v_curv(:,:,3), &
326 v_cart(:,:,1),v_cart(:,:,2),v_cart(:,:,3))
327 END SUBROUTINE convert2cartesian_vectors_2
328
329 PURE SUBROUTINE convert2cartesian_vectors_3(this,curv,v_curv,v_cart)
330 IMPLICIT NONE
331 !------------------------------------------------------------------------!
332 CLASS(geometry_cylindrical), INTENT(IN) :: this
333 REAL, DIMENSION(:,:,:,:), INTENT(IN) :: curv
334 REAL, DIMENSION(:,:,:,:), INTENT(IN) :: v_curv
335 REAL, DIMENSION(:,:,:,:), INTENT(OUT) :: v_cart
336 !------------------------------------------------------------------------!
337 CALL convert2cartesian_vectors(curv(:,:,:,1),curv(:,:,:,2),curv(:,:,:,3), &
338 v_curv(:,:,:,1),v_curv(:,:,:,2),v_curv(:,:,:,3), &
339 v_cart(:,:,:,1),v_cart(:,:,:,2),v_cart(:,:,:,3))
340 END SUBROUTINE convert2cartesian_vectors_3
341
342 PURE SUBROUTINE convert2cartesian_vectors_4(this,curv,v_curv,v_cart)
343 IMPLICIT NONE
344 !------------------------------------------------------------------------!
345 CLASS(geometry_cylindrical), INTENT(IN) :: this
346 REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: curv
347 REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: v_curv
348 REAL, DIMENSION(:,:,:,:,:), INTENT(OUT) :: v_cart
349 !------------------------------------------------------------------------!
350 CALL convert2cartesian_vectors(curv(:,:,:,:,1),curv(:,:,:,:,2),curv(:,:,:,:,3), &
351 v_curv(:,:,:,:,1),v_curv(:,:,:,:,2),v_curv(:,:,:,:,3), &
352 v_cart(:,:,:,:,1),v_cart(:,:,:,:,2),v_cart(:,:,:,:,3))
353 END SUBROUTINE convert2cartesian_vectors_4
354
355 PURE SUBROUTINE convert2curvilinear_vectors_1(this,curv,v_cart,v_curv)
356 IMPLICIT NONE
357 !------------------------------------------------------------------------!
358 CLASS(geometry_cylindrical), INTENT(IN) :: this
359 REAL, DIMENSION(:,:), INTENT(IN) :: curv
360 REAL, DIMENSION(:,:), INTENT(IN) :: v_cart
361 REAL, DIMENSION(:,:), INTENT(OUT) :: v_curv
362 !------------------------------------------------------------------------!
363 CALL convert2curvilinear_vectors(curv(:,1),curv(:,2),curv(:,3), &
364 v_cart(:,1),v_cart(:,2),v_cart(:,3), &
365 v_curv(:,1),v_curv(:,2),v_curv(:,3))
366 END SUBROUTINE convert2curvilinear_vectors_1
367
368 PURE SUBROUTINE convert2curvilinear_vectors_2(this,curv,v_cart,v_curv)
369 IMPLICIT NONE
370 !------------------------------------------------------------------------!
371 CLASS(geometry_cylindrical), INTENT(IN) :: this
372 REAL, DIMENSION(:,:,:), INTENT(IN) :: curv
373 REAL, DIMENSION(:,:,:), INTENT(IN) :: v_cart
374 REAL, DIMENSION(:,:,:), INTENT(OUT) :: v_curv
375 !------------------------------------------------------------------------!
376 CALL convert2curvilinear_vectors(curv(:,:,1),curv(:,:,2),curv(:,:,3), &
377 v_cart(:,:,1),v_cart(:,:,2),v_cart(:,:,3), &
378 v_curv(:,:,1),v_curv(:,:,2),v_curv(:,:,3))
379 END SUBROUTINE convert2curvilinear_vectors_2
380
381 PURE SUBROUTINE convert2curvilinear_vectors_3(this,curv,v_cart,v_curv)
382 IMPLICIT NONE
383 !------------------------------------------------------------------------!
384 CLASS(geometry_cylindrical), INTENT(IN) :: this
385 REAL, DIMENSION(:,:,:,:), INTENT(IN) :: curv
386 REAL, DIMENSION(:,:,:,:), INTENT(IN) :: v_cart
387 REAL, DIMENSION(:,:,:,:), INTENT(OUT) :: v_curv
388 !------------------------------------------------------------------------!
389 CALL convert2curvilinear_vectors(curv(:,:,:,1),curv(:,:,:,2),curv(:,:,:,3), &
390 v_cart(:,:,:,1),v_cart(:,:,:,2),v_cart(:,:,:,3), &
391 v_curv(:,:,:,1),v_curv(:,:,:,2),v_curv(:,:,:,3))
392 END SUBROUTINE convert2curvilinear_vectors_3
393
394 PURE SUBROUTINE convert2curvilinear_vectors_4(this,curv,v_cart,v_curv)
395 IMPLICIT NONE
396 !------------------------------------------------------------------------!
397 CLASS(geometry_cylindrical), INTENT(IN) :: this
398 REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: curv
399 REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: v_cart
400 REAL, DIMENSION(:,:,:,:,:), INTENT(OUT) :: v_curv
401 !------------------------------------------------------------------------!
402 CALL convert2curvilinear_vectors(curv(:,:,:,:,1),curv(:,:,:,:,2),curv(:,:,:,:,3), &
403 v_cart(:,:,:,:,1),v_cart(:,:,:,:,2),v_cart(:,:,:,:,3), &
404 v_curv(:,:,:,:,1),v_curv(:,:,:,:,2),v_curv(:,:,:,:,3))
405 END SUBROUTINE convert2curvilinear_vectors_4
406
407 SUBROUTINE finalize(this)
408 IMPLICIT NONE
409 !------------------------------------------------------------------------!
410 CLASS(geometry_cylindrical), INTENT(INOUT) :: this
411 !------------------------------------------------------------------------!
412 CALL this%Finalize_base()
413 END SUBROUTINE finalize
414
415 ELEMENTAL SUBROUTINE scalefactors(r,hr,hphi,hz)
416 IMPLICIT NONE
417 !------------------------------------------------------------------------!
418 REAL, INTENT(IN) :: r
419 REAL, INTENT(OUT) :: hr,hphi,hz
420 !------------------------------------------------------------------------!
421 hr = 1.
422 hphi = r
423 hz = 1.
424 END SUBROUTINE scalefactors
425
426 ELEMENTAL FUNCTION radius(r,z)
427 IMPLICIT NONE
428 !------------------------------------------------------------------------!
429 REAL, INTENT(IN) :: r,z
430 REAL :: radius
431 !------------------------------------------------------------------------!
432 radius = sqrt(r*r+z*z)
433 END FUNCTION radius
434
435 ELEMENTAL SUBROUTINE positionvector(r,z,rx,ry,rz)
436 IMPLICIT NONE
437 !------------------------------------------------------------------------!
438 REAL, INTENT(IN) :: r,z
439 REAL, INTENT(OUT) :: rx,ry,rz
440 !------------------------------------------------------------------------!
441 rx = radius(r,z)
442 ry = 0.0
443 rz = z
444 END SUBROUTINE positionvector
445
446 ELEMENTAL SUBROUTINE convert2cartesian_coords(r,phi,zz,x,y,z)
447 IMPLICIT NONE
448 !------------------------------------------------------------------------!
449 REAL, INTENT(IN) :: r,phi,zz
450 REAL, INTENT(OUT) :: x,y,z
451 !------------------------------------------------------------------------!
452 x = r*cos(phi)
453 y = r*sin(phi)
454 z = zz
455 END SUBROUTINE convert2cartesian_coords
456
457 ELEMENTAL SUBROUTINE convert2curvilinear_coords(x,y,z,r,phi,zz)
458 IMPLICIT NONE
459 !------------------------------------------------------------------------!
460 REAL, INTENT(IN) :: x,y,z
461 REAL, INTENT(OUT) :: r,phi,zz
462 !------------------------------------------------------------------------!
463 r = sqrt(x*x+y*y)
464 phi = atan2(y,x)
465 IF (phi.LT.0.0) THEN
466 phi = phi + 2.0*pi
467 END IF
468 zz = z
469 END SUBROUTINE convert2curvilinear_coords
470
472 ELEMENTAL SUBROUTINE convert2cartesian_vectors(r,phi,z,vr,vphi,vzz,vx,vy,vz)
473 IMPLICIT NONE
474 !------------------------------------------------------------------------!
475 REAL, INTENT(IN) :: r,phi,z,vr,vphi,vzz
476 REAL, INTENT(OUT) :: vx,vy,vz
477 !------------------------------------------------------------------------!
478 vx = vr*cos(phi) - vphi*sin(phi)
479 vy = vr*sin(phi) + vphi*cos(phi)
480 vz = vzz
481 END SUBROUTINE convert2cartesian_vectors
482
483
485 ELEMENTAL SUBROUTINE convert2curvilinear_vectors(r,phi,z,vx,vy,vz,vr,vphi,vzz)
486 IMPLICIT NONE
487 !------------------------------------------------------------------------!
488 REAL, INTENT(IN) :: r,phi,z,vx,vy,vz
489 REAL, INTENT(OUT) :: vr,vphi,vzz
490 !------------------------------------------------------------------------!
491 vr = vx*cos(phi) + vy*sin(phi)
492 vphi = -vx*sin(phi) + vy*cos(phi)
493 vzz = vz
494 END SUBROUTINE convert2curvilinear_vectors
495
496
Dictionary for generic data types.
Definition: common_dict.f90:61
type(logging_base), save this
base class for geometrical properties
real, parameter, public pi
pure subroutine convert2cartesian_vectors(this, curv, v_curv, v_cart)
Convert curvilinear vector components to cartesian vector components.
integer, parameter, public cylindrical
pure subroutine convert2curvilinear_coords(this, cart, curv)
Convert cartesian to curvilinear coordinates.
pure subroutine convert2curvilinear_vectors(this, curv, v_cart, v_curv)
Convert cartesian vector components to curvilinear vector components.
pure subroutine convert2cartesian_coords(this, curv, cart)
Convert curvilinear to cartesian coordinates.
defines properties of a 3D cylindrical mesh
elemental subroutine positionvector(r, z, rx, ry, rz)
pure subroutine positionvector_3(this, coords, posvec)
character(len=32), parameter geometry_name
pure subroutine convert2cartesian_coords_3(this, curv, cart)
pure subroutine convert2curvilinear_vectors_3(this, curv, v_cart, v_curv)
pure subroutine positionvector_4(this, coords, posvec)
pure subroutine convert2cartesian_coords_2(this, curv, cart)
pure subroutine convert2curvilinear_coords_3(this, cart, curv)
subroutine initgeometry_cylindrical(this, config)
pure subroutine convert2curvilinear_vectors_4(this, curv, v_cart, v_curv)
pure subroutine convert2cartesian_coords_1(this, curv, cart)
pure subroutine radius_4(this, coords, r)
pure subroutine convert2cartesian_vectors_1(this, curv, v_curv, v_cart)
pure subroutine scalefactors_1(this, coords, hx, hy, hz)
pure subroutine scalefactors_2(this, coords, hx, hy, hz)
pure subroutine convert2cartesian_vectors_2(this, curv, v_curv, v_cart)
pure subroutine radius_1(this, coords, r)
pure subroutine convert2curvilinear_coords_4(this, cart, curv)
pure subroutine radius_3(this, coords, r)
pure subroutine positionvector_2(this, coords, posvec)
pure subroutine convert2curvilinear_vectors_1(this, curv, v_cart, v_curv)
pure subroutine convert2cartesian_vectors_4(this, curv, v_curv, v_cart)
pure subroutine convert2cartesian_vectors_3(this, curv, v_curv, v_cart)
pure subroutine convert2curvilinear_vectors_2(this, curv, v_cart, v_curv)
pure subroutine convert2curvilinear_coords_1(this, cart, curv)
pure subroutine positionvector_1(this, coords, posvec)
pure subroutine convert2cartesian_coords_4(this, curv, cart)
pure subroutine scalefactors_3(this, coords, hx, hy, hz)
pure subroutine scalefactors_4(this, coords, hx, hy, hz)
pure subroutine convert2curvilinear_coords_2(this, cart, curv)
elemental real function radius(r, z)
pure subroutine radius_2(this, coords, r)
elemental subroutine scalefactors(r, hr, hphi, hz)