FE-Project
Loading...
Searching...
No Matches
mod_atmos_mesh_gm.F90
Go to the documentation of this file.
1!-------------------------------------------------------------------------------
2!> module Atmosphere / Mesh
3!!
4!! @par Description
5!! Module for mesh with atmospheric global model
6!!
7!! @author Yuta kawai, Team SCALE
8!!
9!<
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
31
34
35 use mod_atmos_mesh, only: &
37
38 !-----------------------------------------------------------------------------
39 implicit none
40 private
41 !-----------------------------------------------------------------------------
42 !
43 !++ Public type & procedures
44 !
45
46 !> Derived type to manage a computational mesh of global atmospheric model
47 !!
48 type, extends(atmosmesh), public :: atmosmeshgm
49 type(meshcubedspheredom3d) :: mesh !< Object for 3D cubed-sphere mesh
51 contains
52 procedure :: init => atmosmeshgm_init
53 procedure :: final => atmosmeshgm_final
54 procedure :: create_communicator => atmosmeshgm_create_communicator
55 procedure :: setup_restartfile1 => atmosmeshgm_setup_restartfile1
56 procedure :: setup_restartfile2 => atmosmeshgm_setup_restartfile2
57 procedure :: calc_uvmet => atmosmeshgm_calc_uvmet
58 procedure :: setup_vcoordinate => atmosmeshgm_setup_vcoordinate
59 end type atmosmeshgm
60
61 !-----------------------------------------------------------------------------
62 !
63 !++ Public parameters & variables
64 !
65
66 !-----------------------------------------------------------------------------
67 !
68 !++ Private procedures
69 !
70 !-------------------
71
72 !-----------------------------------------------------------------------------
73 !
74 !++ Private parameters & variables
75 !
76
77contains
78
79 !> Initialize an object to manage computational mesh
80 !!
81!OCL SERIAL
82 subroutine atmosmeshgm_init( this )
83 use scale_const, only: &
84 rplanet => const_radius
85 use scale_mesh_base2d, only: &
86 mftype2d_xy => meshbase2d_dimtypeid_xy
87 use scale_meshutil_vcoord, only: &
89
90 implicit none
91 class(atmosmeshgm), target, intent(inout) :: this
92
93 real(RP) :: dom_zmin = 0.0_rp !< Minimum vertical coordinate value of the computational domain
94 real(RP) :: dom_zmax = 10.0e3_rp !< Maximum vertical coordinate value of the computational domain
95 logical :: isPeriodicZ = .false. !< Flag whether a periodic boundary condition is applied in the vertical direction
96
97 integer, parameter :: FZ_nmax = 1000
98 real(RP) :: FZ(FZ_nmax) !< Values of the vertically computational coordinate at the element boundaries
99
100 !* Global
101 logical :: SHALLOW_ATM_APPROX_FLAG = .true. !< Flag whether the shallow atmosphere approximation is applied
102 integer :: NeGX = 2 !< Number of finite element in the y-coordinate direction in each panel of the cubed-sphere mesh
103 integer :: NeGY = 2 !< Number of finite element in the y-coordinate direction in each panel of the cubed-sphere mesh
104 integer :: NeZ = 2 !< Number of finite element in the vertical direction in each MPI process
105 integer :: NLocalMeshPerPrc = 6 !< Number of local mesh per MPI process
106 integer :: Nprc = 1 !< Total number of MPI process
107 integer :: PolyOrder_h = 2 !< Polynomial order for the horizontal direction
108 integer :: PolyOrder_v = 2 !< Polynomial order for the z-direction
109 logical :: LumpedMassMatFlag = .false. !< Flag whether a mass lumping is applied
110
111 character(len=H_LONG) :: TOPO_IN_BASENAME = '' !< Basename of the input file
112 character(len=H_MID) :: TOPO_IN_VARNAME = 'topo' !< Variable name of topography in the input file
113 character(len=H_MID) :: VERTICAL_COORD_NAME = "TERRAIN_FOLLOWING" !< Type of the vertical coordinate
114
115 logical :: COMM_USE_MPI_PC = .false. !< Flag whether persistent communication is used in MPI
116 logical :: COMM_USE_MPI_PC_FUJITSU_EXT
117
118 character(len=H_SHORT) :: Element_operation_type = 'General' !< General or TensorProd3D
119 character(len=H_SHORT) :: SpMV_storage_format = 'ELL' !< CSR or ELL
120
121 namelist / param_atmos_mesh / &
122 shallow_atm_approx_flag, &
123 dom_zmin, dom_zmax, &
124 fz, isperiodicz, &
125 negx, negy, nez, nlocalmeshperprc, nprc, &
126 polyorder_h, polyorder_v, lumpedmassmatflag, &
127 element_operation_type, &
128 spmv_storage_format, &
129 vertical_coord_name, &
130 topo_in_basename, topo_in_varname, &
131 comm_use_mpi_pc, &
132 comm_use_mpi_pc_fujitsu_ext
133
134 integer :: k
135 logical :: is_spec_FZ
136
137 integer :: ierr
138
139 type(file_base_meshfield) :: file_topo
140 !-------------------------------------------
141
142 log_newline
143 log_info("ATMOS_MESH_setup",*) 'Setup'
144
145 fz(:) = -1.0_rp
146#ifdef __FUJITSU
147 comm_use_mpi_pc_fujitsu_ext = .true.
148#else
149 comm_use_mpi_pc_fujitsu_ext = .false.
150#endif
151
152 rewind(io_fid_conf)
153 read(io_fid_conf,nml=param_atmos_mesh,iostat=ierr)
154 if( ierr < 0 ) then !--- missing
155 log_info("ATMOS_MESH_setup",*) 'Not found namelist. Default used.'
156 elseif( ierr > 0 ) then !--- fatal error
157 log_error("ATMOS_MESH_setup",*) 'Not appropriate names in namelist PARAM_ATM_MESH. Check!'
158 call prc_abort
159 endif
160 log_nml(param_atmos_mesh)
161
162 !----
163
164 !- Setup the element
165
166 call this%element%Init( polyorder_h, polyorder_v, lumpedmassmatflag )
167 call this%element_v1D%Init( polyorder_v, lumpedmassmatflag )
168
169 !- Setup the mesh
170
171 is_spec_fz = .true.
172 do k=1, nez+1
173 if (fz(k) < 0.0_rp) then
174 is_spec_fz = .false.
175 end if
176 end do
177 if (is_spec_fz) then
178 call this%mesh%Init( &
179 negx, negy, nez, rplanet, dom_zmin, dom_zmax, &
180 this%element, nlocalmeshperprc, nproc=nprc, &
181 fz=fz(1:nez+1), shallow_approx=shallow_atm_approx_flag )
182 else
183 call this%mesh%Init( &
184 negx, negy, nez, rplanet, dom_zmin, dom_zmax, &
185 this%element, nlocalmeshperprc, nproc=nprc, &
186 shallow_approx=shallow_atm_approx_flag )
187 end if
188
189 call this%mesh%Generate()
190
191 !-
192
193 call this%AtmosMesh_Init( this%mesh )
194 call this%PrepairElementOperation( element_operation_type, spmv_storage_format )
195
196 !- Set topography & vertical coordinate
197
198 if ( topo_in_basename /= '' ) then
199 log_info("ATMOS_MESH_setup",*) 'Read topography data'
200
201 call file_topo%Init(1, meshcubedsphere2d=this%mesh%mesh2D )
202 call file_topo%Open( topo_in_basename, myrank=prc_myrank )
203 call file_topo%Read_Var( mftype2d_xy, topo_in_varname, this%topography%topo )
204 call file_topo%Close()
205 call file_topo%Final()
206 end if
207
208 this%vcoord_type_id = meshutil_get_vcoord_typeid( vertical_coord_name )
209 call this%Setup_vcoordinate()
210
211 !-
212 this%comm_use_mpi_pc = comm_use_mpi_pc
213 this%comm_use_mpi_pc_fujitsu_ext = comm_use_mpi_pc_fujitsu_ext
214
215 return
216 end subroutine atmosmeshgm_init
217
218 !> Finalize an object to manage computational mesh
219 !!
220!OCL SERIAL
221 subroutine atmosmeshgm_final(this)
222 implicit none
223
224 class(atmosmeshgm), intent(inout) :: this
225 integer :: commid
226 !-------------------------------------------
227
228 do commid=1, this%communicator_num
229 call this%comm_list(commid)%Final()
230 end do
231
232 call this%mesh%Final()
233 call this%AtmosMesh_Final()
234
235 return
236 end subroutine atmosmeshgm_final
237
238 !> Create a communicator for data communication on global computational domain
239 !!
240!OCL SERIAL
241 subroutine atmosmeshgm_create_communicator( this, sfield_num, hvfield_num, htensorfield_num, &
242 var_manager, field_list, commid )
243 implicit none
244 class(atmosmeshgm), target, intent(inout) :: this
245 integer, intent(in) :: sfield_num !< Number of scalar fields
246 integer, intent(in) :: hvfield_num !< Number of horizontal vector fields
247 integer, intent(in) :: htensorfield_num !< Number of horizontal tensor fields
248 class(modelvarmanager), intent(inout) :: var_manager !< Object to manage variables
249 class(meshfield3d), intent(in) :: field_list(:) !< Array of 3D fields
250 integer, intent(out) :: commid !< Communicator ID
251 !-----------------------------------------------------
252
253 commid = this%Get_communicatorID( atm_mesh_max_commnuicator_num )
254 call this%comm_list(commid)%Init( sfield_num, hvfield_num, htensorfield_num, this%mesh )
255 if ( this%comm_use_mpi_pc ) then
256 call this%comm_list(commid)%Prepare_PC( this%comm_use_mpi_pc_fujitsu_ext )
257 end if
258 call var_manager%MeshFieldComm_Prepare( this%comm_list(commid), field_list )
259
260 return
261 end subroutine atmosmeshgm_create_communicator
262
263!OCL SERIAL
264 subroutine atmosmeshgm_setup_restartfile1( this, restart_file, var_num )
265 implicit none
266 class(atmosmeshgm), target, intent(inout) :: this
267 class(file_restart_meshfield_component), intent(inout) :: restart_file
268 integer, intent(in) :: var_num
269 !------------------------------------------------
270
271 call restart_file%Init('ATMOS', var_num, meshcubedsphere3d=this%mesh )
272 return
273 end subroutine atmosmeshgm_setup_restartfile1
274
275!OCL SERIAL
276 subroutine atmosmeshgm_setup_restartfile2( this, restart_file, &
277 in_basename, in_postfix_timelabel, &
278 out_basename, out_postfix_timelabel, &
279 out_dtype, out_title, var_num )
280 implicit none
281 class(atmosmeshgm), target, intent(inout) :: this
282 class(file_restart_meshfield_component), intent(inout) :: restart_file
283 character(*), intent(in) :: in_basename
284 logical, intent(in) :: in_postfix_timelabel
285 character(*), intent(in) :: out_basename
286 logical, intent(in) :: out_postfix_timelabel
287 character(*), intent(in) :: out_title
288 character(*), intent(in) :: out_dtype
289 integer, intent(in) :: var_num
290 !-----------------------------------------------------------
291
292 call restart_file%Init('ATMOS', in_basename, in_postfix_timelabel, &
293 out_basename, out_postfix_timelabel, out_dtype, out_title, var_num, &
294 meshcubedsphere3d=this%mesh )
295
296 end subroutine atmosmeshgm_setup_restartfile2
297
298!> Calculate horizontal vector components in longitude-latitude coordinates
299!OCL SERIAL
300 subroutine atmosmeshgm_calc_uvmet( this, U, V, &
301 Umet, Vmet )
302
303 use scale_cubedsphere_coord_cnv, only: &
305 implicit none
306 class(atmosmeshgm), target, intent(in) :: this
307 type(meshfield3d), intent(in) :: U
308 type(meshfield3d), intent(in) :: V
309 type(meshfield3d), intent(inout) :: Umet
310 type(meshfield3d), intent(inout) :: Vmet
311
312 integer :: n
313 integer :: ke, ke2D
314 type(localmesh3d), pointer :: lcmesh
315 class(elementbase3d), pointer :: elem
316 !------------------------------------------
317
318 do n=1, this%mesh%LOCAL_MESH_NUM
319 lcmesh => this%mesh%lcmesh_list(n)
320 elem => lcmesh%refElem3D
322 lcmesh%panelID, lcmesh%pos_en(:,:,1), lcmesh%pos_en(:,:,2), & ! (in)
323 lcmesh%gam, elem%Np * lcmesh%Ne, & ! (in)
324 u%local(n)%val(:,lcmesh%NeS:lcmesh%NeE), & ! (in)
325 v%local(n)%val(:,lcmesh%NeS:lcmesh%NeE), & ! (in)
326 umet%local(n)%val(:,lcmesh%NeS:lcmesh%NeE), & ! (out)
327 vmet%local(n)%val(:,lcmesh%NeS:lcmesh%NeE) ) ! (out)
328 end do
329
330 return
331 end subroutine atmosmeshgm_calc_uvmet
332
333!> Setup the vertical coordinate
334!OCL SERIAL
335 subroutine atmosmeshgm_setup_vcoordinate( this )
337 implicit none
338 class(atmosmeshgm), TARGET, INTENT(INOUT) :: this
339
340 type(meshfieldcommcubedspheredom3d) :: comm3D
341 type(meshfieldcommcubedspheredom2d) :: comm2D
342 !-------------------------------------------------
343
344 call comm2d%Init( 1, 0, 0, this%mesh%mesh2D )
345 call comm3d%Init( 2, 1, 0, this%mesh )
346
347 call this%topography%SetVCoordinate( this%ptr_mesh, &
348 this%vcoord_type_id, this%mesh%zmax_gl, comm3d, comm2d )
349
350 call comm2d%Final()
351 call comm3d%Final()
352
353 return
354 end SUBROUTINE atmosmeshgm_setup_vcoordinate
355
356end module mod_atmos_mesh_gm
module Atmosphere / Mesh
subroutine atmosmeshgm_init(this)
Initialize an object to manage computational mesh.
module Atmosphere / Mesh
integer, parameter, public atm_mesh_max_commnuicator_num
Module common / Coordinate conversion with cubed-sphere projection.
subroutine, public cubedspherecoordcnv_cs2lonlatvec(panelid, alpha, beta, gam, np, vecalpha, vecbeta, veclon, veclat, lat)
Covert the components of a vector in local coordinates with an equiangular gnomonic cubed-sphere proj...
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 / Cubed-sphere 3D domain
module FElib / Data / base
module FElib / Data / Communication in 2D cubed-sphere domain
module FElib / Data / Communication in 3D cubed-sphere 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 (base class)
Derived type to manage a computational mesh of global atmospheric model.
Derived type representing a 3D reference element.
Derived type representing a hexahedral element.
Derived type to manage a local 3D computational domain.
Derived type representing a field with 3D mesh.
Base derived type to manage data communication with 2D cubed-sphere domain.
Base derived type to manage data communication with 3D cubed-sphere domain.
Derived type to manage a sparse matrix.