MAMMA  1.0
Conduitsolver
geometry.f90
Go to the documentation of this file.
1 !*********************************************************************
3 !
6 !*********************************************************************
7 MODULE geometry
8 
9  IMPLICIT NONE
10 
12  REAL*8, ALLOCATABLE :: z_comp(:)
13 
15  REAL*8, ALLOCATABLE :: z_stag(:)
16 
18  REAL*8, ALLOCATABLE :: radius_stag(:)
19 
20  REAL*8 :: z0
21  REAL*8 :: zn
22  REAL*8 :: zeta_exit
23  REAL*8 :: dz
24 
25  REAL*8 :: pi
26 
27  REAL*8 :: radius
28 
36  CHARACTER*30 :: radius_model
37 
38  REAL*8 :: radius_fixed
39  REAL*8 :: radius_min
40  REAL*8 :: radius_max
41  REAL*8 :: radius_z
42  REAL*8 :: radius_z_sig
43 
44  INTEGER :: comp_cells
45  INTEGER :: comp_interfaces
46 
47 CONTAINS
48 
49  !*********************************************************************
51  !
54  !*********************************************************************
55 
56  SUBROUTINE init_grid
57 
58  IMPLICIT none
59 
60  INTEGER j
61 
62  pi = 4.d0 * datan(1.d0)
63 
65 
66  ALLOCATE( z_comp(comp_cells) )
67  ALLOCATE( z_stag(comp_interfaces) )
68  ALLOCATE( radius_stag(comp_interfaces) )
69 
70  dz = ( zn - z0 ) / comp_cells
71 
72  z_stag(1) = z0
73  z_comp(1) = z0 + 0.5 * dz
74 
75  DO j=1,comp_cells
76 
77  z_stag(j+1) = min( z_stag(j) + dz , zn )
78 
79  z_comp(j) = 0.5 * ( z_stag(j) + z_stag(j+1) )
80 
81  END DO
82 
83  SELECT CASE ( radius_model )
84 
85  CASE DEFAULT
86 
88 
89 
90  CASE ('fixed' )
91 
93 
94  CASE ( 'linear' )
95 
96  DO j=1,comp_interfaces
97 
98  radius_stag(j) = radius_min + (radius_max - radius_min) * z_stag(j) / (zn - z0)
99 
100  END DO
101 
102  CASE ( 'trans1' )
103 
104  DO j=1,comp_interfaces
105 
106  IF( z_stag(j) > (radius_z + radius_z_sig) ) THEN
107 
109 
110  ELSEIF( z_stag(j) < (radius_z - radius_z_sig) ) THEN
111 
113 
114  ELSE
115 
117  ( z_stag(j) - radius_z + radius_z_sig) / (2.d0 * radius_z_sig)
118 
119  END IF
120 
121  END DO
122 
123  CASE ( 'trans2' )
124 
125  DO j=1,comp_interfaces
126 
127  IF( z_stag(j) > (radius_z + radius_z_sig) ) THEN
128 
130 
131  ELSEIF( z_stag(j) > (radius_z) ) THEN
132 
134  ( z_stag(j) - radius_z ) / ( radius_z_sig )
135 
136  ELSEIF( z_stag(j) > (radius_z - radius_z_sig) ) THEN
137 
139  ( z_stag(j) - radius_z + radius_z_sig) / ( radius_z_sig )
140 
141  ELSE
142 
144 
145  END IF
146 
147  END DO
148 
149  CASE ( 'external' )
150 
151  OPEN( unit=10, file='DataRadius.txt' )
152 
153  DO j=1,comp_interfaces
154 
155  READ(10,*) radius_stag(j)
156 
157  END DO
158 
159  CLOSE(10)
160 
161  END SELECT
162 
163  END SUBROUTINE init_grid
164 
165  SUBROUTINE update_radius(zeta)
167  IMPLICIT NONE
168 
169  REAL*8, INTENT(IN) :: zeta
170  REAL*8 :: coeff_interp
171  INTEGER :: j , z_idx
172 
173  z_idx = 1
174 
175  DO j=1,comp_interfaces-1
176 
177  IF ( z_stag(j) < zeta ) z_idx = j
178 
179  END DO
180 
181  ! zeta is between z_stag(j) and z_stag(j+1)
182 
183  coeff_interp = ( zeta - z_stag(z_idx) ) / ( z_stag(z_idx+1) - z_stag(z_idx) )
184 
185  radius = coeff_interp * radius_stag(z_idx+1) + ( 1.d0 - coeff_interp ) * &
186  radius_stag(z_idx)
187 
188  END SUBROUTINE update_radius
189 
190 END MODULE geometry
real *8 dz
Control volumes size.
Definition: geometry.f90:23
real *8 radius_max
Fixed value of the maximum radius (used in non cylindrical conduits)
Definition: geometry.f90:40
integer comp_cells
Number of control volumes in the computational domain.
Definition: geometry.f90:44
subroutine update_radius(zeta)
Definition: geometry.f90:166
real *8, dimension(:), allocatable z_stag
Location of the boundaries of the control volumes of the domain.
Definition: geometry.f90:15
real *8 pi
Definition: geometry.f90:25
real *8 z0
Left (bottom) of the physical domain.
Definition: geometry.f90:20
real *8 radius_fixed
Fixed value of the radius.
Definition: geometry.f90:38
real *8 radius_z_sig
Characteristic sigma for radius model trans1 and trans2.
Definition: geometry.f90:42
real *8 radius
Effective radius.
Definition: geometry.f90:27
real *8, dimension(:), allocatable radius_stag
Radius at the boundaries of the control volumes of the domain.
Definition: geometry.f90:18
real *8 zeta_exit
Right (top) of the physical domain.
Definition: geometry.f90:22
real *8, dimension(:), allocatable z_comp
Location of the centers of the control volume of the domain.
Definition: geometry.f90:12
integer comp_interfaces
Number of interfaces (comp_cells+1)
Definition: geometry.f90:45
real *8 zn
Right (top) of the physical domain.
Definition: geometry.f90:21
character *30 radius_model
geometry model
Definition: geometry.f90:36
subroutine init_grid
Finite volume grid initialization.
Definition: geometry.f90:57
real *8 radius_z
Characteristic depth for radius models trans1 and trans2.
Definition: geometry.f90:41
Grid module.
Definition: geometry.f90:7
real *8 radius_min
Fixed value of the minimum radius (used in non cylindrical conduits)
Definition: geometry.f90:39