FE-Project
All Classes Namespaces Files Functions Variables Pages
mod_atmos_mesh_rm.F90
Go to the documentation of this file.
1!-------------------------------------------------------------------------------
10!-------------------------------------------------------------------------------
11#include "scaleFElib.h"
13 !-----------------------------------------------------------------------------
14 !
15 !++ Used modules
16 !
17 use scale_precision
18 use scale_io
19 use scale_prc
20
28 use scale_sparsemat, only: sparsemat
30
33
34 use mod_atmos_mesh, only: &
36
37 !-----------------------------------------------------------------------------
38 implicit none
39 private
40 !-----------------------------------------------------------------------------
41 !
42 !++ Public type & procedures
43 !
44
47 type, extends(atmosmesh), public :: atmosmeshrm
48 type(meshcubedom3d) :: mesh
50 contains
51 procedure :: init => atmosmeshrm_init
52 procedure :: final => atmosmeshrm_final
53 procedure :: create_communicator => atmosmeshrm_create_communicator
54 procedure :: setup_restartfile1 => atmosmeshrm_setup_restartfile1
55 procedure :: setup_restartfile2 => atmosmeshrm_setup_restartfile2
56 procedure :: calc_uvmet => atmosmeshrm_calc_uvmet
57 procedure :: setup_vcoordinate => atmosmeshrm_setup_vcoordinate
58 end type atmosmeshrm
59
60 !-----------------------------------------------------------------------------
61 !
62 !++ Public parameters & variables
63 !
64
65 !-----------------------------------------------------------------------------
66 !
67 !++ Private procedures
68 !
69 !-------------------
70
71 !-----------------------------------------------------------------------------
72 !
73 !++ Private parameters & variables
74 !
75
76contains
77
78 !- AtmosMesh RM -----------------------------------------
79
82 subroutine atmosmeshrm_init( this )
84 use scale_mesh_base2d, only: &
85 mftype2d_xy => meshbase2d_dimtypeid_xy
86 use scale_meshutil_vcoord, only: &
88
89 implicit none
90 class(atmosmeshrm), target, intent(inout) :: this
91
92 real(RP) :: dom_xmin = 0.0_rp
93 real(RP) :: dom_xmax = 100.0e3_rp
94 real(RP) :: dom_ymin = 0.0_rp
95 real(RP) :: dom_ymax = 100.0e3_rp
96 real(RP) :: dom_zmin = 0.0_rp
97 real(RP) :: dom_zmax = 10.0e3_rp
98 logical :: isPeriodicX = .true.
99 logical :: isPeriodicY = .true.
100 logical :: isPeriodicZ = .false.
101
102 integer :: NeX = 2
103 integer :: NeY = 2
104 integer :: NeZ = 2
105 integer :: NprcX = 1
106 integer :: NprcY = 1
107 integer :: PolyOrder_h = 2
108 integer :: PolyOrder_v = 2
109 logical :: LumpedMassMatFlag = .false.
110
111 character(len=H_LONG) :: TOPO_IN_BASENAME = ''
112 character(len=H_MID) :: TOPO_IN_VARNAME = 'topo'
113 character(len=H_MID) :: VERTICAL_COORD_NAME = "TERRAIN_FOLLOWING"
114
115 logical :: COMM_USE_MPI_PC = .false.
116
117 character(len=H_SHORT) :: Element_operation_type = 'General'
118 character(len=H_SHORT) :: SpMV_storage_format = 'ELL'
119
120 integer, parameter :: ATMOS_MESH_NLocalMeshPerPrc = 1
121
122 integer, parameter :: FZ_nmax = 1000
123 real(RP) :: FZ(FZ_nmax)
124
125 namelist / param_atmos_mesh / &
126 dom_xmin, dom_xmax, &
127 dom_ymin, dom_ymax, &
128 dom_zmin, dom_zmax, &
129 fz, &
130 isperiodicx, isperiodicy, isperiodicz, &
131 nex, ney, nez, &
132 polyorder_h, polyorder_v, lumpedmassmatflag, &
133 element_operation_type, &
134 spmv_storage_format, &
135 nprcx, nprcy, &
136 topo_in_basename, topo_in_varname, &
137 vertical_coord_name, &
138 comm_use_mpi_pc
139
140 integer :: k
141 logical :: is_spec_FZ
142
143 integer :: ierr
144
145 type(file_base_meshfield) :: file_topo
146 !-------------------------------------------
147
148 log_newline
149 log_info("ATMOS_MESH_setup",*) 'Setup'
150
151 fz(:) = -1.0_rp
152
153 rewind(io_fid_conf)
154 read(io_fid_conf,nml=param_atmos_mesh,iostat=ierr)
155 if( ierr < 0 ) then !--- missing
156 log_info("ATMOS_MESH_setup",*) 'Not found namelist. Default used.'
157 elseif( ierr > 0 ) then !--- fatal error
158 log_error("ATMOS_MESH_setup",*) 'Not appropriate names in namelist PARAM_ATM_MESH. Check!'
159 call prc_abort
160 endif
161 log_nml(param_atmos_mesh)
162
163 !----
164
165 ! Setup the element
166
167 call this%element%Init( polyorder_h, polyorder_v, lumpedmassmatflag )
168 call this%element_v1D%Init( polyorder_v, lumpedmassmatflag )
169
170 ! Setup the mesh
171
172 is_spec_fz = .true.
173 do k=1, nez+1
174 if (fz(k) < 0.0_rp) then
175 is_spec_fz = .false.
176 end if
177 end do
178 if (is_spec_fz) then
179 call this%mesh%Init( &
180 nprcx*nex, nprcy*ney, nez, &
181 dom_xmin, dom_xmax,dom_ymin, dom_ymax, dom_zmin, dom_zmax, &
182 isperiodicx, isperiodicy, isperiodicz, &
183 this%element, atmos_mesh_nlocalmeshperprc, nprcx, nprcy, &
184 fz=fz(1:nez+1) )
185 else
186 call this%mesh%Init( &
187 nprcx*nex, nprcy*ney, nez, &
188 dom_xmin, dom_xmax,dom_ymin, dom_ymax, dom_zmin, dom_zmax, &
189 isperiodicx, isperiodicy, isperiodicz, &
190 this%element, atmos_mesh_nlocalmeshperprc, nprcx, nprcy )
191 end if
192
193 call this%mesh%Generate()
194
195 !-
196 call this%AtmosMesh_Init( this%mesh )
197 call this%PrepairElementOperation( element_operation_type, spmv_storage_format )
198
199 !- Set topography & vertical coordinate
200
201 if ( topo_in_basename /= '' ) then
202 log_info("ATMOS_MESH_setup",*) 'Read topography data'
203
204 call file_topo%Init(1, mesh2d=this%mesh%mesh2D )
205 call file_topo%Open( topo_in_basename, myrank=prc_myrank )
206 call file_topo%Read_Var( mftype2d_xy, topo_in_varname, this%topography%topo )
207 call file_topo%Close()
208 call file_topo%Final()
209 end if
210
211 this%vcoord_type_id = meshutil_get_vcoord_typeid( vertical_coord_name )
212 call this%Setup_vcoordinate()
213
214 !-
215 this%comm_use_mpi_pc = comm_use_mpi_pc
216
217 return
218 end subroutine atmosmeshrm_init
219
222 subroutine atmosmeshrm_final(this)
223 implicit none
224
225 class(atmosmeshrm), intent(inout) :: this
226 integer :: commid
227 !-------------------------------------------
228
229 do commid=1, this%communicator_num
230 call this%comm_list(commid)%Final()
231 end do
232
233 call this%mesh%Final()
234 call this%AtmosMesh_Final()
235
236 return
237 end subroutine atmosmeshrm_final
238
239 subroutine atmosmeshrm_create_communicator( this, sfield_num, hvfield_num, htensorfield_num, &
240 var_manager, field_list, commid )
241 implicit none
242 class(atmosmeshrm), target, intent(inout) :: this
243 integer, intent(in) :: sfield_num
244 integer, intent(in) :: hvfield_num
245 integer, intent(in) :: htensorfield_num
246 class(modelvarmanager), intent(inout) :: var_manager
247 class(meshfield3d), intent(in) :: field_list(:)
248 integer, intent(out) :: commid
249 !-----------------------------------------------------
250
251 commid = this%Get_communicatorID( atm_mesh_max_commnuicator_num )
252 call this%comm_list(commid)%Init(sfield_num, hvfield_num, htensorfield_num, this%mesh )
253 if ( this%comm_use_mpi_pc ) call this%comm_list(commid)%Prepare_PC()
254 call var_manager%MeshFieldComm_Prepair( this%comm_list(commid), field_list )
255
256 return
257 end subroutine atmosmeshrm_create_communicator
258
259 subroutine atmosmeshrm_setup_restartfile1( this, restart_file, var_num )
260 implicit none
261 class(atmosmeshrm), target, intent(inout) :: this
262 class(file_restart_meshfield_component), intent(inout) :: restart_file
263 integer, intent(in) :: var_num
264 !------------------------------------------------
265
266 call restart_file%Init('ATMOS', var_num, mesh3d=this%mesh )
267 return
268 end subroutine atmosmeshrm_setup_restartfile1
269
270 subroutine atmosmeshrm_setup_restartfile2( this, restart_file, &
271 in_basename, in_postfix_timelabel, &
272 out_basename, out_postfix_timelabel, &
273 out_dtype, out_title, var_num )
274 implicit none
275 class(atmosmeshrm), target, intent(inout) :: this
276 class(file_restart_meshfield_component), intent(inout) :: restart_file
277 character(*), intent(in) :: in_basename
278 logical, intent(in) :: in_postfix_timelabel
279 character(*), intent(in) :: out_basename
280 logical, intent(in) :: out_postfix_timelabel
281 character(*), intent(in) :: out_title
282 character(*), intent(in) :: out_dtype
283 integer, intent(in) :: var_num
284 !-----------------------------------------------------------
285
286 call restart_file%Init('ATMOS', in_basename, in_postfix_timelabel, &
287 out_basename, out_postfix_timelabel, out_dtype, out_title, var_num, &
288 mesh3d=this%mesh )
289
290 return
291 end subroutine atmosmeshrm_setup_restartfile2
292
293 subroutine atmosmeshrm_calc_uvmet( this, U, V, &
294 Umet, Vmet )
295 implicit none
296 class(atmosmeshrm), target, intent(in) :: this
297 type(meshfield3d), intent(in) :: U
298 type(meshfield3d), intent(in) :: V
299 type(meshfield3d), intent(inout) :: Umet
300 type(meshfield3d), intent(inout) :: Vmet
301
302 integer :: n
303 integer :: ke
304 type(localmesh3d), pointer :: lcmesh
305 !------------------------------------------
306
307 do n=1, this%mesh%LOCAL_MESH_NUM
308 lcmesh => this%mesh%lcmesh_list(n)
309 !$omp parallel do
310 do ke=lcmesh%NeS, lcmesh%NeE
311 umet%local(n)%val(:,ke) = u%local(n)%val(:,ke)
312 vmet%local(n)%val(:,ke) = v%local(n)%val(:,ke)
313 end do
314 end do
315
316 return
317 end subroutine atmosmeshrm_calc_uvmet
318
319 subroutine atmosmeshrm_setup_vcoordinate( this )
321 implicit none
322 class(atmosmeshrm), TARGET, INTENT(INOUT) :: this
323
324 type(meshfieldcommcubedom3d) :: comm3D
325 type(meshfieldcommrectdom2d) :: comm2D
326 !-------------------------------------------------
327
328 call comm2d%Init( 1, 0, 0, this%mesh%mesh2D )
329 call comm3d%Init( 2, 1, 0, this%mesh )
330
331 call this%topography%SetVCoordinate( this%ptr_mesh, &
332 this%vcoord_type_id, this%mesh%zmax_gl, comm3d, comm2d )
333
334 call comm2d%Final()
335 call comm3d%Final()
336
337 return
338 end SUBROUTINE atmosmeshrm_setup_vcoordinate
339
340end module mod_atmos_mesh_rm
module Atmosphere / Mesh
subroutine atmosmeshrm_init(this)
Initialize a object to manage computational mesh.
module Atmosphere / Mesh
integer, parameter, public atm_mesh_max_commnuicator_num
module FElib / Element / Base
module FElib / Element / hexahedron
module FElib / Mesh / Local 3D
module FElib / Mesh / Base 2D
integer, public meshbase2d_dimtypeid_xy
module FElib / Mesh / Base 3D
module FElib / Mesh / Cubic 3D domain
module FElib / Data / base
module FElib / Data / Communication 3D cubic domain
module FElib / Data / Communication 2D rectangle domain
module FElib / Mesh / utility for general vertical coordinate
integer function, public meshutil_get_vcoord_typeid(vcoord_type)
FElib / model framework / mesh manager.
FElib / model framework / variable manager.
module common / sparsemat
Derived type to manage a computational mesh of regional atmospheric model.