geometry_cartesian.f90
Go to the documentation of this file.
1 !#############################################################################
2 !# #
3 !# fosite - 3D hydrodynamical simulation program #
4 !# module: geometry_cartesian.f90 #
5 !# #
6 !# Copyright (C) 2007-2010 #
7 !# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
8 !# Jannes Klee <jklee@astrophysik.uni-kiel.de> #
9 !# #
10 !# This program is free software; you can redistribute it and/or modify #
11 !# it under the terms of the GNU General Public License as published by #
12 !# the Free Software Foundation; either version 2 of the License, or (at #
13 !# your option) any later version. #
14 !# #
15 !# This program is distributed in the hope that it will be useful, but #
16 !# WITHOUT ANY WARRANTY; without even the implied warranty of #
17 !# MERCHANTABILITY OR FITNESS FOR A PARTICULAR PURPOSE, GOOD TITLE or #
18 !# NON INFRINGEMENT. See the GNU General Public License for more #
19 !# details. #
20 !# #
21 !# You should have received a copy of the GNU General Public License #
22 !# along with this program; if not, write to the Free Software #
23 !# Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. #
24 !# #
25 !#############################################################################
26 
27 !----------------------------------------------------------------------------!
35 !----------------------------------------------------------------------------!
38  USE common_dict
39  IMPLICIT NONE
40  !--------------------------------------------------------------------------!
41  TYPE, EXTENDS (geometry_base) :: geometry_cartesian
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 = "cartesian"
76  !--------------------------------------------------------------------------!
77  PUBLIC :: geometry_cartesian
78  !--------------------------------------------------------------------------!
79 
80 CONTAINS
81 
82  SUBROUTINE initgeometry_cartesian(this,config)
83  IMPLICIT NONE
84  !------------------------------------------------------------------------!
85  CLASS(geometry_cartesian), INTENT(INOUT) :: this
86  TYPE(DICT_TYP),POINTER :: config
87  !------------------------------------------------------------------------!
88  REAL :: dz
89  !------------------------------------------------------------------------!
90  CALL this%InitGeometry(cartesian,geometry_name,config)
91  CALL getattr(config, "dz", dz, 1.0)
92  END SUBROUTINE initgeometry_cartesian
93 
94  PURE SUBROUTINE scalefactors_1(this,coords,hx,hy,hz)
95  IMPLICIT NONE
96  !------------------------------------------------------------------------!
97  CLASS(geometry_cartesian), INTENT(IN) :: this
98  REAL, INTENT(IN), DIMENSION(:,:) :: coords
99  REAL, INTENT(OUT), DIMENSION(:) :: hx,hy,hz
100  !------------------------------------------------------------------------!
101  CALL scalefactors(coords(:,1),coords(:,2),coords(:,3),hx(:),hy(:),hz(:))
102  END SUBROUTINE scalefactors_1
103 
104  PURE SUBROUTINE scalefactors_2(this,coords,hx,hy,hz)
105  IMPLICIT NONE
106  !------------------------------------------------------------------------!
107  CLASS(geometry_cartesian), INTENT(IN) :: this
108  REAL, INTENT(IN), DIMENSION(:,:,:) :: coords
109  REAL, INTENT(OUT), DIMENSION(:,:) :: hx,hy,hz
110  !------------------------------------------------------------------------!
111  CALL scalefactors(coords(:,:,1),coords(:,:,2),coords(:,:,3), &
112  hx(:,:),hy(:,:),hz(:,:))
113  END SUBROUTINE scalefactors_2
114 
115  PURE SUBROUTINE scalefactors_3(this,coords,hx,hy,hz)
116  IMPLICIT NONE
117  !------------------------------------------------------------------------!
118  CLASS(geometry_cartesian), INTENT(IN) :: this
119  REAL, INTENT(IN), DIMENSION(:,:,:,:) :: coords
120  REAL, INTENT(OUT), DIMENSION(:,:,:) :: hx,hy,hz
121  !------------------------------------------------------------------------!
122  CALL scalefactors(coords(:,:,:,1),coords(:,:,:,2),coords(:,:,:,3), &
123  hx(:,:,:),hy(:,:,:),hz(:,:,:))
124  END SUBROUTINE scalefactors_3
125 
126  PURE SUBROUTINE scalefactors_4(this,coords,hx,hy,hz)
127  IMPLICIT NONE
128  !------------------------------------------------------------------------!
129  CLASS(geometry_cartesian), INTENT(IN) :: this
130  REAL, INTENT(IN), DIMENSION(:,:,:,:,:) :: coords
131  REAL, INTENT(OUT), DIMENSION(:,:,:,:) :: hx,hy,hz
132  !------------------------------------------------------------------------!
133  CALL scalefactors(coords(:,:,:,:,1),coords(:,:,:,:,2),coords(:,:,:,:,3), &
134  hx(:,:,:,:),hy(:,:,:,:),hz(:,:,:,:))
135  END SUBROUTINE scalefactors_4
136 
137  PURE SUBROUTINE radius_1(this,coords,r)
138  IMPLICIT NONE
139  !------------------------------------------------------------------------!
140  CLASS(geometry_cartesian), INTENT(IN) :: this
141  REAL, DIMENSION(:,:), INTENT(IN) :: coords
142  REAL, DIMENSION(:), INTENT(OUT) :: r
143  !------------------------------------------------------------------------!
144  r = radius(coords(:,1),coords(:,2),coords(:,3))
145  END SUBROUTINE radius_1
146 
147  PURE SUBROUTINE radius_2(this,coords,r)
148  IMPLICIT NONE
149  !------------------------------------------------------------------------!
150  CLASS(geometry_cartesian), INTENT(IN) :: this
151  REAL, DIMENSION(:,:,:), INTENT(IN) :: coords
152  REAL, DIMENSION(:,:), INTENT(OUT) :: r
153  !------------------------------------------------------------------------!
154  r = radius(coords(:,:,1),coords(:,:,2),coords(:,:,3))
155  END SUBROUTINE radius_2
156 
157  PURE SUBROUTINE radius_3(this,coords,r)
158  IMPLICIT NONE
159  !------------------------------------------------------------------------!
160  CLASS(geometry_cartesian), INTENT(IN) :: this
161  REAL, DIMENSION(:,:,:,:), INTENT(IN) :: coords
162  REAL, DIMENSION(:,:,:), INTENT(OUT) :: r
163  !------------------------------------------------------------------------!
164  r = radius(coords(:,:,:,1),coords(:,:,:,2),coords(:,:,:,3))
165  END SUBROUTINE radius_3
166 
167  PURE SUBROUTINE radius_4(this,coords,r)
168  IMPLICIT NONE
169  !------------------------------------------------------------------------!
170  CLASS(geometry_cartesian), INTENT(IN) :: this
171  REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: coords
172  REAL, DIMENSION(:,:,:,:), INTENT(OUT) :: r
173  !------------------------------------------------------------------------!
174  r = radius(coords(:,:,:,:,1),coords(:,:,:,:,2),coords(:,:,:,:,3))
175  END SUBROUTINE radius_4
176 
177  PURE SUBROUTINE positionvector_1(this,coords,posvec)
178  IMPLICIT NONE
179  !------------------------------------------------------------------------!
180  CLASS(geometry_cartesian), INTENT(IN) :: this
181  REAL, DIMENSION(:,:), INTENT(IN) :: coords
182  REAL, DIMENSION(:,:), INTENT(OUT) :: posvec
183  !------------------------------------------------------------------------!
184  posvec = coords
185  END SUBROUTINE positionvector_1
186 
187  PURE SUBROUTINE positionvector_2(this,coords,posvec)
188  IMPLICIT NONE
189  !------------------------------------------------------------------------!
190  CLASS(geometry_cartesian), INTENT(IN) :: this
191  REAL, DIMENSION(:,:,:), INTENT(IN) :: coords
192  REAL, DIMENSION(:,:,:), INTENT(OUT) :: posvec
193  !------------------------------------------------------------------------!
194  posvec = coords
195  END SUBROUTINE positionvector_2
196 
197  PURE SUBROUTINE positionvector_3(this,coords,posvec)
198  IMPLICIT NONE
199  !------------------------------------------------------------------------!
200  CLASS(geometry_cartesian), INTENT(IN) :: this
201  REAL, DIMENSION(:,:,:,:), INTENT(IN) :: coords
202  REAL, DIMENSION(:,:,:,:), INTENT(OUT) :: posvec
203  !------------------------------------------------------------------------!
204  posvec = coords
205  END SUBROUTINE positionvector_3
206 
207  PURE SUBROUTINE positionvector_4(this,coords,posvec)
208  IMPLICIT NONE
209  !------------------------------------------------------------------------!
210  CLASS(geometry_cartesian), INTENT(IN) :: this
211  REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: coords
212  REAL, DIMENSION(:,:,:,:,:), INTENT(OUT) :: posvec
213  !------------------------------------------------------------------------!
214  posvec = coords
215  END SUBROUTINE positionvector_4
216 
217  PURE SUBROUTINE convert2cartesian_coords_1(this,curv,cart)
218  IMPLICIT NONE
219  !------------------------------------------------------------------------!
220  CLASS(geometry_cartesian), INTENT(IN) :: this
221  REAL, DIMENSION(:,:), INTENT(IN) :: curv
222  REAL, DIMENSION(:,:), INTENT(OUT) :: cart
223  !------------------------------------------------------------------------!
224  cart = curv
225  END SUBROUTINE convert2cartesian_coords_1
226 
227  PURE SUBROUTINE convert2cartesian_coords_2(this,curv,cart)
228  IMPLICIT NONE
229  !------------------------------------------------------------------------!
230  CLASS(geometry_cartesian), INTENT(IN) :: this
231  REAL, DIMENSION(:,:,:), INTENT(IN) :: curv
232  REAL, DIMENSION(:,:,:), INTENT(OUT) :: cart
233  !------------------------------------------------------------------------!
234  cart = curv
235  END SUBROUTINE convert2cartesian_coords_2
236 
237  PURE SUBROUTINE convert2cartesian_coords_3(this,curv,cart)
238  IMPLICIT NONE
239  !------------------------------------------------------------------------!
240  CLASS(geometry_cartesian), INTENT(IN) :: this
241  REAL, DIMENSION(:,:,:,:), INTENT(IN) :: curv
242  REAL, DIMENSION(:,:,:,:), INTENT(OUT) :: cart
243  !------------------------------------------------------------------------!
244  cart = curv
245  END SUBROUTINE convert2cartesian_coords_3
246 
247  PURE SUBROUTINE convert2cartesian_coords_4(this,curv,cart)
248  IMPLICIT NONE
249  !------------------------------------------------------------------------!
250  CLASS(geometry_cartesian), INTENT(IN) :: this
251  REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: curv
252  REAL, DIMENSION(:,:,:,:,:), INTENT(OUT) :: cart
253  !------------------------------------------------------------------------!
254  cart = curv
255  END SUBROUTINE convert2cartesian_coords_4
256 
257  PURE SUBROUTINE convert2curvilinear_coords_1(this,cart,curv)
258  IMPLICIT NONE
259  !------------------------------------------------------------------------!
260  CLASS(geometry_cartesian), INTENT(IN) :: this
261  REAL, DIMENSION(:,:), INTENT(IN) :: cart
262  REAL, DIMENSION(:,:), INTENT(OUT) :: curv
263  !------------------------------------------------------------------------!
264  curv = cart
265  END SUBROUTINE convert2curvilinear_coords_1
266 
267  PURE SUBROUTINE convert2curvilinear_coords_2(this,cart,curv)
268  IMPLICIT NONE
269  !------------------------------------------------------------------------!
270  CLASS(geometry_cartesian), INTENT(IN) :: this
271  REAL, DIMENSION(:,:,:), INTENT(IN) :: cart
272  REAL, DIMENSION(:,:,:), INTENT(OUT) :: curv
273  !------------------------------------------------------------------------!
274  curv = cart
275  END SUBROUTINE convert2curvilinear_coords_2
276 
277  PURE SUBROUTINE convert2curvilinear_coords_3(this,cart,curv)
278  IMPLICIT NONE
279  !------------------------------------------------------------------------!
280  CLASS(geometry_cartesian), INTENT(IN) :: this
281  REAL, DIMENSION(:,:,:,:), INTENT(IN) :: cart
282  REAL, DIMENSION(:,:,:,:), INTENT(OUT) :: curv
283  !------------------------------------------------------------------------!
284  curv = cart
285  END SUBROUTINE convert2curvilinear_coords_3
286 
287  PURE SUBROUTINE convert2curvilinear_coords_4(this,cart,curv)
288  IMPLICIT NONE
289  !------------------------------------------------------------------------!
290  CLASS(geometry_cartesian), INTENT(IN) :: this
291  REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: cart
292  REAL, DIMENSION(:,:,:,:,:), INTENT(OUT) :: curv
293  !------------------------------------------------------------------------!
294  curv = cart
295  END SUBROUTINE convert2curvilinear_coords_4
296 
297  ! vector transformations
298  PURE SUBROUTINE convert2cartesian_vectors_1(this,curv,v_curv,v_cart)
299  IMPLICIT NONE
300  !------------------------------------------------------------------------!
301  CLASS(geometry_cartesian), INTENT(IN) :: this
302  REAL, DIMENSION(:,:), INTENT(IN) :: curv
303  REAL, DIMENSION(:,:), INTENT(IN) :: v_curv
304  REAL, DIMENSION(:,:), INTENT(OUT) :: v_cart
305  !------------------------------------------------------------------------!
306  v_cart = v_curv
307  END SUBROUTINE convert2cartesian_vectors_1
308 
309  PURE SUBROUTINE convert2cartesian_vectors_2(this,curv,v_curv,v_cart)
310  IMPLICIT NONE
311  !------------------------------------------------------------------------!
312  CLASS(geometry_cartesian), INTENT(IN) :: this
313  REAL, DIMENSION(:,:,:), INTENT(IN) :: curv
314  REAL, DIMENSION(:,:,:), INTENT(IN) :: v_curv
315  REAL, DIMENSION(:,:,:), INTENT(OUT) :: v_cart
316  !------------------------------------------------------------------------!
317  v_cart = v_curv
318  END SUBROUTINE convert2cartesian_vectors_2
319 
320  PURE SUBROUTINE convert2cartesian_vectors_3(this,curv,v_curv,v_cart)
321  IMPLICIT NONE
322  !------------------------------------------------------------------------!
323  CLASS(geometry_cartesian), INTENT(IN) :: this
324  REAL, DIMENSION(:,:,:,:), INTENT(IN) :: curv
325  REAL, DIMENSION(:,:,:,:), INTENT(IN) :: v_curv
326  REAL, DIMENSION(:,:,:,:), INTENT(OUT) :: v_cart
327  !------------------------------------------------------------------------!
328  v_cart = v_curv
329  END SUBROUTINE convert2cartesian_vectors_3
330 
331  PURE SUBROUTINE convert2cartesian_vectors_4(this,curv,v_curv,v_cart)
332  IMPLICIT NONE
333  !------------------------------------------------------------------------!
334  CLASS(geometry_cartesian), INTENT(IN) :: this
335  REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: curv
336  REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: v_curv
337  REAL, DIMENSION(:,:,:,:,:), INTENT(OUT) :: v_cart
338  !------------------------------------------------------------------------!
339  v_cart = v_curv
340  END SUBROUTINE convert2cartesian_vectors_4
341 
342  PURE SUBROUTINE convert2curvilinear_vectors_1(this,curv,v_cart,v_curv)
343  IMPLICIT NONE
344  !------------------------------------------------------------------------!
345  CLASS(geometry_cartesian), INTENT(IN) :: this
346  REAL, DIMENSION(:,:), INTENT(IN) :: curv
347  REAL, DIMENSION(:,:), INTENT(IN) :: v_cart
348  REAL, DIMENSION(:,:), INTENT(OUT) :: v_curv
349  !------------------------------------------------------------------------!
350  v_curv = v_cart
351  END SUBROUTINE convert2curvilinear_vectors_1
352 
353  PURE SUBROUTINE convert2curvilinear_vectors_2(this,curv,v_cart,v_curv)
354  IMPLICIT NONE
355  !------------------------------------------------------------------------!
356  CLASS(geometry_cartesian), INTENT(IN) :: this
357  REAL, DIMENSION(:,:,:), INTENT(IN) :: curv
358  REAL, DIMENSION(:,:,:), INTENT(IN) :: v_cart
359  REAL, DIMENSION(:,:,:), INTENT(OUT) :: v_curv
360  !------------------------------------------------------------------------!
361  v_curv = v_cart
362  END SUBROUTINE convert2curvilinear_vectors_2
363 
364  PURE SUBROUTINE convert2curvilinear_vectors_3(this,curv,v_cart,v_curv)
365  IMPLICIT NONE
366  !------------------------------------------------------------------------!
367  CLASS(geometry_cartesian), INTENT(IN) :: this
368  REAL, DIMENSION(:,:,:,:), INTENT(IN) :: curv
369  REAL, DIMENSION(:,:,:,:), INTENT(IN) :: v_cart
370  REAL, DIMENSION(:,:,:,:), INTENT(OUT) :: v_curv
371  !------------------------------------------------------------------------!
372  v_curv = v_cart
373  END SUBROUTINE convert2curvilinear_vectors_3
374 
375  PURE SUBROUTINE convert2curvilinear_vectors_4(this,curv,v_cart,v_curv)
376  IMPLICIT NONE
377  !------------------------------------------------------------------------!
378  CLASS(geometry_cartesian), INTENT(IN) :: this
379  REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: curv
380  REAL, DIMENSION(:,:,:,:,:), INTENT(IN) :: v_cart
381  REAL, DIMENSION(:,:,:,:,:), INTENT(OUT) :: v_curv
382  !------------------------------------------------------------------------!
383  v_curv = v_cart
384  END SUBROUTINE convert2curvilinear_vectors_4
385 
386  SUBROUTINE finalize(this)
387  IMPLICIT NONE
388  !------------------------------------------------------------------------!
389  CLASS(geometry_cartesian), INTENT(INOUT) :: this
390  !------------------------------------------------------------------------!
391  CALL this%Finalize_base()
392  END SUBROUTINE finalize
393 
394  ELEMENTAL SUBROUTINE scalefactors(x,y,z,hx,hy,hz)
395  IMPLICIT NONE
396  !------------------------------------------------------------------------!
397  REAL, INTENT(IN) :: x,y,z
398  REAL, INTENT(OUT) :: hx,hy,hz
399  !------------------------------------------------------------------------!
400  hx = 1.
401  hy = 1.
402  hz = 1.
403  END SUBROUTINE scalefactors
404 
405  ELEMENTAL FUNCTION radius(x,y,z)
406  IMPLICIT NONE
407  !------------------------------------------------------------------------!
408  REAL, INTENT(IN) :: x,y,z
409  REAL :: radius
410  !------------------------------------------------------------------------!
411  radius = sqrt(x*x+y*y+z*z)
412  END FUNCTION radius
413 
414 END MODULE geometry_cartesian_mod
subroutine finalize(this)
Destructor of common class.
pure subroutine convert2curvilinear_vectors_1(this, curv, v_cart, v_curv)
pure subroutine scalefactors_4(this, coords, hx, hy, hz)
pure subroutine radius_2(this, coords, r)
elemental subroutine scalefactors(x, y, z, hx, hy, hz)
pure subroutine convert2curvilinear_coords_2(this, cart, curv)
type(logging_base), save this
pure subroutine scalefactors_3(this, coords, hx, hy, hz)
pure subroutine convert2curvilinear_coords_4(this, cart, curv)
pure subroutine positionvector_2(this, coords, posvec)
pure subroutine scalefactors_1(this, coords, hx, hy, hz)
pure subroutine radius_4(this, coords, r)
pure subroutine convert2curvilinear_coords_3(this, cart, curv)
character(len=32), parameter geometry_name
pure subroutine positionvector_3(this, coords, posvec)
pure subroutine convert2cartesian_vectors_3(this, curv, v_curv, v_cart)
pure subroutine positionvector_4(this, coords, posvec)
pure subroutine convert2curvilinear_coords_1(this, cart, curv)
integer, parameter, public cartesian
elemental real function radius(x, y, z)
base class for geometrical properties
pure subroutine radius_1(this, coords, r)
pure subroutine convert2cartesian_vectors_1(this, curv, v_curv, v_cart)
pure subroutine convert2cartesian_coords_1(this, curv, cart)
pure subroutine scalefactors_2(this, coords, hx, hy, hz)
defines properties of a 3D cartesian mesh
pure subroutine convert2cartesian_coords_4(this, curv, cart)
pure subroutine convert2curvilinear_vectors_3(this, curv, v_cart, v_curv)
pure subroutine convert2curvilinear_vectors_2(this, curv, v_cart, v_curv)
Dictionary for generic data types.
Definition: common_dict.f90:61
pure subroutine radius_3(this, coords, r)
subroutine initgeometry_cartesian(this, config)
pure subroutine positionvector_1(this, coords, posvec)
pure subroutine convert2cartesian_coords_3(this, curv, cart)
pure subroutine convert2cartesian_coords_2(this, curv, cart)
pure subroutine convert2curvilinear_vectors_4(this, curv, v_cart, v_curv)
pure subroutine convert2cartesian_vectors_2(this, curv, v_curv, v_cart)
pure subroutine convert2cartesian_vectors_4(this, curv, v_curv, v_cart)