11#include "scaleFElib.h"
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
83 use scale_const,
only: &
84 rplanet => const_radius
93 real(RP) :: dom_zmin = 0.0_rp
94 real(RP) :: dom_zmax = 10.0e3_rp
95 logical :: isPeriodicZ = .false.
97 integer,
parameter :: FZ_nmax = 1000
98 real(RP) :: FZ(FZ_nmax)
101 logical :: SHALLOW_ATM_APPROX_FLAG = .true.
105 integer :: NLocalMeshPerPrc = 6
107 integer :: PolyOrder_h = 2
108 integer :: PolyOrder_v = 2
109 logical :: LumpedMassMatFlag = .false.
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"
115 logical :: COMM_USE_MPI_PC = .false.
116 logical :: COMM_USE_MPI_PC_FUJITSU_EXT
118 character(len=H_SHORT) :: Element_operation_type =
'General'
119 character(len=H_SHORT) :: SpMV_storage_format =
'ELL'
121 namelist / param_atmos_mesh / &
122 shallow_atm_approx_flag, &
123 dom_zmin, dom_zmax, &
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, &
132 comm_use_mpi_pc_fujitsu_ext
135 logical :: is_spec_FZ
143 log_info(
"ATMOS_MESH_setup",*)
'Setup'
147 comm_use_mpi_pc_fujitsu_ext = .true.
149 comm_use_mpi_pc_fujitsu_ext = .false.
153 read(io_fid_conf,nml=param_atmos_mesh,iostat=ierr)
155 log_info(
"ATMOS_MESH_setup",*)
'Not found namelist. Default used.'
156 elseif( ierr > 0 )
then
157 log_error(
"ATMOS_MESH_setup",*)
'Not appropriate names in namelist PARAM_ATM_MESH. Check!'
160 log_nml(param_atmos_mesh)
166 call this%element%Init( polyorder_h, polyorder_v, lumpedmassmatflag )
167 call this%element_v1D%Init( polyorder_v, lumpedmassmatflag )
173 if (fz(k) < 0.0_rp)
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 )
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 )
189 call this%mesh%Generate()
193 call this%AtmosMesh_Init( this%mesh )
194 call this%PrepairElementOperation( element_operation_type, spmv_storage_format )
198 if ( topo_in_basename /=
'' )
then
199 log_info(
"ATMOS_MESH_setup",*)
'Read topography data'
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()
209 call this%Setup_vcoordinate()
212 this%comm_use_mpi_pc = comm_use_mpi_pc
213 this%comm_use_mpi_pc_fujitsu_ext = comm_use_mpi_pc_fujitsu_ext
221 subroutine atmosmeshgm_final(this)
228 do commid=1, this%communicator_num
229 call this%comm_list(commid)%Final()
232 call this%mesh%Final()
233 call this%AtmosMesh_Final()
236 end subroutine atmosmeshgm_final
241 subroutine atmosmeshgm_create_communicator( this, sfield_num, hvfield_num, htensorfield_num, &
242 var_manager, field_list, commid )
245 integer,
intent(in) :: sfield_num
246 integer,
intent(in) :: hvfield_num
247 integer,
intent(in) :: htensorfield_num
250 integer,
intent(out) :: commid
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 )
258 call var_manager%MeshFieldComm_Prepare( this%comm_list(commid), field_list )
261 end subroutine atmosmeshgm_create_communicator
264 subroutine atmosmeshgm_setup_restartfile1( this, restart_file, var_num )
268 integer,
intent(in) :: var_num
271 call restart_file%Init(
'ATMOS', var_num, meshcubedsphere3d=this%mesh )
273 end subroutine atmosmeshgm_setup_restartfile1
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 )
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
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 )
296 end subroutine atmosmeshgm_setup_restartfile2
300 subroutine atmosmeshgm_calc_uvmet( this, U, V, &
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), &
323 lcmesh%gam, elem%Np * lcmesh%Ne, &
324 u%local(n)%val(:,lcmesh%NeS:lcmesh%NeE), &
325 v%local(n)%val(:,lcmesh%NeS:lcmesh%NeE), &
326 umet%local(n)%val(:,lcmesh%NeS:lcmesh%NeE), &
327 vmet%local(n)%val(:,lcmesh%NeS:lcmesh%NeE) )
331 end subroutine atmosmeshgm_calc_uvmet
335 subroutine atmosmeshgm_setup_vcoordinate( this )
344 call comm2d%Init( 1, 0, 0, this%mesh%mesh2D )
345 call comm3d%Init( 2, 1, 0, this%mesh )
347 call this%topography%SetVCoordinate( this%ptr_mesh, &
348 this%vcoord_type_id, this%mesh%zmax_gl, comm3d, comm2d )
354 end SUBROUTINE atmosmeshgm_setup_vcoordinate
subroutine atmosmeshgm_init(this)
Initialize an object to manage computational 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 / File / Base
module FElib / File / Restart
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.