85 CLASS(geometry_cylindrical),
INTENT(INOUT) :: this
86 TYPE(DICT_TYP),
POINTER :: config
89 CALL this%SetAzimuthIndex(2)
96 REAL,
INTENT(IN),
DIMENSION(:,:) :: coords
97 REAL,
INTENT(OUT),
DIMENSION(:) :: hx,hy,hz
106 REAL,
INTENT(IN),
DIMENSION(:,:,:) :: coords
107 REAL,
INTENT(OUT),
DIMENSION(:,:) :: hx,hy,hz
109 CALL scalefactors(coords(:,:,1),hx(:,:),hy(:,:),hz(:,:))
116 REAL,
INTENT(IN),
DIMENSION(:,:,:,:) :: coords
117 REAL,
INTENT(OUT),
DIMENSION(:,:,:) :: hx,hy,hz
119 CALL scalefactors(coords(:,:,:,1),hx(:,:,:),hy(:,:,:),hz(:,:,:))
126 REAL,
INTENT(IN),
DIMENSION(:,:,:,:,:) :: coords
127 REAL,
INTENT(OUT),
DIMENSION(:,:,:,:) :: hx,hy,hz
129 CALL scalefactors(coords(:,:,:,:,1),hx(:,:,:,:),hy(:,:,:,:),hz(:,:,:,:))
132 PURE SUBROUTINE radius_1(this,coords,r)
136 REAL,
DIMENSION(:,:),
INTENT(IN) :: coords
137 REAL,
DIMENSION(:),
INTENT(OUT) :: r
139 r =
radius(coords(:,1),coords(:,3))
142 PURE SUBROUTINE radius_2(this,coords,r)
146 REAL,
DIMENSION(:,:,:),
INTENT(IN) :: coords
147 REAL,
DIMENSION(:,:),
INTENT(OUT) :: r
149 r =
radius(coords(:,:,1),coords(:,:,3))
152 PURE SUBROUTINE radius_3(this,coords,r)
156 REAL,
DIMENSION(:,:,:,:),
INTENT(IN) :: coords
157 REAL,
DIMENSION(:,:,:),
INTENT(OUT) :: r
159 r =
radius(coords(:,:,:,1),coords(:,:,:,3))
162 PURE SUBROUTINE radius_4(this,coords,r)
166 REAL,
DIMENSION(:,:,:,:,:),
INTENT(IN) :: coords
167 REAL,
DIMENSION(:,:,:,:),
INTENT(OUT) :: r
169 r =
radius(coords(:,:,:,:,1),coords(:,:,:,:,3))
176 REAL,
DIMENSION(:,:),
INTENT(IN) :: coords
177 REAL,
DIMENSION(:,:),
INTENT(OUT) :: posvec
179 CALL positionvector(coords(:,1),coords(:,3),posvec(:,1),posvec(:,2),posvec(:,3))
186 REAL,
DIMENSION(:,:,:),
INTENT(IN) :: coords
187 REAL,
DIMENSION(:,:,:),
INTENT(OUT) :: posvec
190 posvec(:,:,2),posvec(:,:,3))
197 REAL,
DIMENSION(:,:,:,:),
INTENT(IN) :: coords
198 REAL,
DIMENSION(:,:,:,:),
INTENT(OUT) :: posvec
200 CALL positionvector(coords(:,:,:,1),coords(:,:,:,3),posvec(:,:,:,1), &
201 posvec(:,:,:,2),posvec(:,:,:,3))
208 REAL,
DIMENSION(:,:,:,:,:),
INTENT(IN) :: coords
209 REAL,
DIMENSION(:,:,:,:,:),
INTENT(OUT) :: posvec
211 CALL positionvector(coords(:,:,:,:,1),coords(:,:,:,:,3),posvec(:,:,:,:,1), &
212 posvec(:,:,:,:,2),posvec(:,:,:,:,3))
219 REAL,
DIMENSION(:,:),
INTENT(IN) :: curv
220 REAL,
DIMENSION(:,:),
INTENT(OUT) :: cart
223 cart(:,1),cart(:,2),cart(:,3))
230 REAL,
DIMENSION(:,:,:),
INTENT(IN) :: curv
231 REAL,
DIMENSION(:,:,:),
INTENT(OUT) :: cart
234 cart(:,:,1),cart(:,:,2),cart(:,:,3))
241 REAL,
DIMENSION(:,:,:,:),
INTENT(IN) :: curv
242 REAL,
DIMENSION(:,:,:,:),
INTENT(OUT) :: cart
244 CALL convert2cartesian_coords(curv(:,:,:,1),curv(:,:,:,2),curv(:,:,:,3), &
245 cart(:,:,:,1),cart(:,:,:,2),cart(:,:,:,3))
252 REAL,
DIMENSION(:,:,:,:,:),
INTENT(IN) :: curv
253 REAL,
DIMENSION(:,:,:,:,:),
INTENT(OUT) :: cart
255 CALL convert2cartesian_coords(curv(:,:,:,:,1),curv(:,:,:,:,2),curv(:,:,:,:,3), &
256 cart(:,:,:,:,1),cart(:,:,:,:,2),cart(:,:,:,:,3))
263 REAL,
DIMENSION(:,:),
INTENT(IN) :: cart
264 REAL,
DIMENSION(:,:),
INTENT(OUT) :: curv
267 curv(:,1),curv(:,2),curv(:,3))
274 REAL,
DIMENSION(:,:,:),
INTENT(IN) :: cart
275 REAL,
DIMENSION(:,:,:),
INTENT(OUT) :: curv
278 curv(:,:,1),curv(:,:,2),curv(:,:,3))
285 REAL,
DIMENSION(:,:,:,:),
INTENT(IN) :: cart
286 REAL,
DIMENSION(:,:,:,:),
INTENT(OUT) :: curv
288 CALL convert2curvilinear_coords(cart(:,:,:,1),cart(:,:,:,2),cart(:,:,:,3), &
289 curv(:,:,:,1),curv(:,:,:,2),curv(:,:,:,3))
296 REAL,
DIMENSION(:,:,:,:,:),
INTENT(IN) :: cart
297 REAL,
DIMENSION(:,:,:,:,:),
INTENT(OUT) :: curv
299 CALL convert2curvilinear_coords(cart(:,:,:,:,1),cart(:,:,:,:,2),cart(:,:,:,:,3), &
300 curv(:,:,:,:,1),curv(:,:,:,:,2),curv(:,:,:,:,3))
307 REAL,
DIMENSION(:,:),
INTENT(IN) :: curv
308 REAL,
DIMENSION(:,:),
INTENT(IN) :: v_curv
309 REAL,
DIMENSION(:,:),
INTENT(OUT) :: v_cart
312 v_curv(:,1),v_curv(:,2),v_curv(:,3), &
313 v_cart(:,1),v_cart(:,2),v_cart(:,3))
320 REAL,
DIMENSION(:,:,:),
INTENT(IN) :: curv
321 REAL,
DIMENSION(:,:,:),
INTENT(IN) :: v_curv
322 REAL,
DIMENSION(:,:,:),
INTENT(OUT) :: v_cart
325 v_curv(:,:,1),v_curv(:,:,2),v_curv(:,:,3), &
326 v_cart(:,:,1),v_cart(:,:,2),v_cart(:,:,3))
333 REAL,
DIMENSION(:,:,:,:),
INTENT(IN) :: curv
334 REAL,
DIMENSION(:,:,:,:),
INTENT(IN) :: v_curv
335 REAL,
DIMENSION(:,:,:,:),
INTENT(OUT) :: v_cart
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))
346 REAL,
DIMENSION(:,:,:,:,:),
INTENT(IN) :: curv
347 REAL,
DIMENSION(:,:,:,:,:),
INTENT(IN) :: v_curv
348 REAL,
DIMENSION(:,:,:,:,:),
INTENT(OUT) :: v_cart
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))
359 REAL,
DIMENSION(:,:),
INTENT(IN) :: curv
360 REAL,
DIMENSION(:,:),
INTENT(IN) :: v_cart
361 REAL,
DIMENSION(:,:),
INTENT(OUT) :: v_curv
364 v_cart(:,1),v_cart(:,2),v_cart(:,3), &
365 v_curv(:,1),v_curv(:,2),v_curv(:,3))
372 REAL,
DIMENSION(:,:,:),
INTENT(IN) :: curv
373 REAL,
DIMENSION(:,:,:),
INTENT(IN) :: v_cart
374 REAL,
DIMENSION(:,:,:),
INTENT(OUT) :: v_curv
377 v_cart(:,:,1),v_cart(:,:,2),v_cart(:,:,3), &
378 v_curv(:,:,1),v_curv(:,:,2),v_curv(:,:,3))
385 REAL,
DIMENSION(:,:,:,:),
INTENT(IN) :: curv
386 REAL,
DIMENSION(:,:,:,:),
INTENT(IN) :: v_cart
387 REAL,
DIMENSION(:,:,:,:),
INTENT(OUT) :: v_curv
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))
398 REAL,
DIMENSION(:,:,:,:,:),
INTENT(IN) :: curv
399 REAL,
DIMENSION(:,:,:,:,:),
INTENT(IN) :: v_cart
400 REAL,
DIMENSION(:,:,:,:,:),
INTENT(OUT) :: v_curv
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))
410 CLASS(geometry_cylindrical),
INTENT(INOUT) :: this
412 CALL this%Finalize_base()
418 REAL,
INTENT(IN) :: r
419 REAL,
INTENT(OUT) :: hr,hphi,hz
426 ELEMENTAL FUNCTION radius(r,z)
429 REAL,
INTENT(IN) :: r,z
438 REAL,
INTENT(IN) :: r,z
439 REAL,
INTENT(OUT) :: rx,ry,rz
449 REAL,
INTENT(IN) :: r,phi,zz
450 REAL,
INTENT(OUT) :: x,y,z
460 REAL,
INTENT(IN) :: x,y,z
461 REAL,
INTENT(OUT) :: r,phi,zz
475 REAL,
INTENT(IN) :: r,phi,z,vr,vphi,vzz
476 REAL,
INTENT(OUT) :: vx,vy,vz
478 vx = vr*cos(phi) - vphi*sin(phi)
479 vy = vr*sin(phi) + vphi*cos(phi)
488 REAL,
INTENT(IN) :: r,phi,z,vx,vy,vz
489 REAL,
INTENT(OUT) :: vr,vphi,vzz
491 vr = vx*cos(phi) + vy*sin(phi)
492 vphi = -vx*sin(phi) + vy*cos(phi)
subroutine finalize(this)
Destructor of common class.
pure subroutine convert2curvilinear_vectors_2(this, curv, v_cart, v_curv)
type(logging_base), save this
pure subroutine convert2cartesian_vectors(this, curv, v_curv, v_cart)
Convert curvilinear vector components to cartesian vector components.
pure subroutine convert2curvilinear_coords_3(this, cart, curv)
pure subroutine convert2cartesian_vectors_3(this, curv, v_curv, v_cart)
pure subroutine radius_4(this, coords, r)
pure subroutine positionvector_4(this, coords, posvec)
pure subroutine scalefactors_2(this, coords, hx, hy, hz)
pure subroutine convert2cartesian_vectors_2(this, curv, v_curv, v_cart)
defines properties of a 3D cylindrical mesh
pure subroutine positionvector_1(this, coords, posvec)
pure subroutine radius_1(this, coords, r)
elemental subroutine positionvector(r, z, rx, ry, rz)
pure subroutine convert2curvilinear_vectors_1(this, curv, v_cart, v_curv)
pure subroutine radius_3(this, coords, r)
pure subroutine convert2curvilinear_vectors_3(this, curv, v_cart, v_curv)
pure subroutine convert2cartesian_coords_3(this, curv, cart)
real, parameter, public pi
base class for geometrical properties
pure subroutine convert2cartesian_coords_2(this, curv, cart)
subroutine initgeometry_cylindrical(this, config)
pure subroutine convert2cartesian_vectors_4(this, curv, v_curv, v_cart)
pure subroutine convert2curvilinear_coords_4(this, cart, curv)
pure subroutine convert2curvilinear_vectors_4(this, curv, v_cart, v_curv)
elemental subroutine scalefactors(r, hr, hphi, hz)
pure subroutine convert2cartesian_coords(this, curv, cart)
Convert curvilinear to cartesian coordinates.
pure subroutine convert2curvilinear_coords_1(this, cart, curv)
pure subroutine convert2cartesian_coords_4(this, curv, cart)
Dictionary for generic data types.
pure subroutine scalefactors_1(this, coords, hx, hy, hz)
pure subroutine scalefactors_3(this, coords, hx, hy, hz)
pure subroutine convert2curvilinear_vectors(this, curv, v_cart, v_curv)
Convert cartesian vector components to curvilinear vector components.
pure subroutine convert2curvilinear_coords_2(this, cart, curv)
character(len=32), parameter geometry_name
pure subroutine convert2cartesian_coords_1(this, curv, cart)
pure subroutine radius_2(this, coords, r)
integer, parameter, public cylindrical
pure subroutine convert2cartesian_vectors_1(this, curv, v_curv, v_cart)
pure subroutine convert2curvilinear_coords(this, cart, curv)
Convert cartesian to curvilinear coordinates.
elemental real function radius(r, z)
pure subroutine scalefactors_4(this, coords, hx, hy, hz)
pure subroutine positionvector_3(this, coords, posvec)
pure subroutine positionvector_2(this, coords, posvec)