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