SCALE-RM
scale_topography.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
9 !-------------------------------------------------------------------------------
11  !-----------------------------------------------------------------------------
12  !
13  !++ used modules
14  !
15  use scale_precision
16  use scale_stdio
17  use scale_prof
19  !-----------------------------------------------------------------------------
20  implicit none
21  private
22  !-----------------------------------------------------------------------------
23  !
24  !++ Public procedure
25  !
26  public :: topo_setup
27  public :: topo_fillhalo
28  public :: topo_write
29 
30  !-----------------------------------------------------------------------------
31  !
32  !++ Public parameters & variables
33  !
34  logical, public :: topo_exist = .false.
35 
36  real(RP), public, allocatable :: topo_zsfc(:,:)
37 
38  !-----------------------------------------------------------------------------
39  !
40  !++ Private procedure
41  !
42  private :: topo_read
43 
44  !-----------------------------------------------------------------------------
45  !
46  !++ Private parameters & variables
47  !
48  character(len=H_LONG), private :: topo_in_basename = ''
49  logical, private :: topo_in_check_coordinates = .false.
50  character(len=H_LONG), private :: topo_out_basename = ''
51  character(len=H_MID), private :: topo_out_title = 'SCALE-RM TOPOGRAPHY'
52  character(len=H_SHORT), private :: topo_out_dtype = 'DEFAULT'
53 
54  !-----------------------------------------------------------------------------
55 contains
56  !-----------------------------------------------------------------------------
58  subroutine topo_setup
59  use scale_process, only: &
61  implicit none
62 
63  namelist / param_topo / &
64  topo_in_basename, &
65  topo_in_check_coordinates, &
66  topo_out_basename, &
67  topo_out_dtype
68 
69  integer :: ierr
70  !---------------------------------------------------------------------------
71 
72  if( io_l ) write(io_fid_log,*)
73  if( io_l ) write(io_fid_log,*) '++++++ Module[TOPOGRAPHY] / Categ[ATMOS-RM GRID] / Origin[SCALElib]'
74 
75  !--- read namelist
76  rewind(io_fid_conf)
77  read(io_fid_conf,nml=param_topo,iostat=ierr)
78  if( ierr < 0 ) then !--- missing
79  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
80  elseif( ierr > 0 ) then !--- fatal error
81  write(*,*) 'xxx Not appropriate names in namelist PARAM_TOPO. Check!'
82  call prc_mpistop
83  endif
84  if( io_nml ) write(io_fid_nml,nml=param_topo)
85 
86  allocate( topo_zsfc(ia,ja) )
87  topo_zsfc(:,:) = 0.0_rp
88 
89  ! read from file
90  call topo_read
91 
92  return
93  end subroutine topo_setup
94 
95  !-----------------------------------------------------------------------------
97  subroutine topo_fillhalo( Zsfc )
98  use scale_comm, only: &
99  comm_vars8, &
100  comm_wait
101  implicit none
102  real(RP), intent(inout), optional :: zsfc(ia,ja)
103  !---------------------------------------------------------------------------
104 
105  if ( present(zsfc) ) then
106  call comm_vars8( zsfc(:,:), 1 )
107  call comm_wait ( zsfc(:,:), 1 )
108  else
109  call comm_vars8( topo_zsfc(:,:), 1 )
110  call comm_wait ( topo_zsfc(:,:), 1 )
111  end if
112 
113  return
114  end subroutine topo_fillhalo
115 
116  !-----------------------------------------------------------------------------
118  subroutine topo_read
119  use scale_fileio, only: &
120  fileio_open, &
121  fileio_read, &
122  fileio_flush, &
123  fileio_check_coordinates, &
125  use scale_process, only: &
127  implicit none
128 
129  integer :: fid
130  !---------------------------------------------------------------------------
131 
132  if( io_l ) write(io_fid_log,*)
133  if( io_l ) write(io_fid_log,*) '*** Input topography file ***'
134 
135  if ( topo_in_basename /= '' ) then
136 
137  call fileio_open( fid, topo_in_basename )
138  call fileio_read( topo_zsfc(:,:), & ! [OUT]
139  fid, 'TOPO', 'XY', step=1 ) ! [IN]
140  call fileio_flush( fid )
141 
142  if ( topo_in_check_coordinates ) then
143  call fileio_check_coordinates( fid )
144  end if
145 
146  call fileio_close( fid )
147 
148  call topo_fillhalo
149 
150  topo_exist = .true.
151 
152  else
153  if( io_l ) write(io_fid_log,*) '*** topography file is not specified.'
154 
155  topo_exist = .false.
156  endif
157 
158  return
159  end subroutine topo_read
160 
161  !-----------------------------------------------------------------------------
163  subroutine topo_write
164  use scale_fileio, only: &
165  fileio_write
166  implicit none
167  !---------------------------------------------------------------------------
168 
169  if ( topo_out_basename /= '' ) then
170 
171  if( io_l ) write(io_fid_log,*)
172  if( io_l ) write(io_fid_log,*) '*** Output topography file ***'
173 
174  call fileio_write( topo_zsfc(:,:), topo_out_basename, topo_out_title, & ! [IN]
175  'TOPO', 'Topography', 'm', 'XY', topo_out_dtype, & ! [IN]
176  nozcoord=.true. )
177 
178  endif
179 
180  return
181  end subroutine topo_write
182 
183 end module scale_topography
subroutine, public topo_write
Write topography.
subroutine, public topo_fillhalo(Zsfc)
HALO Communication.
subroutine, public prc_mpistop
Abort MPI.
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:61
subroutine, public fileio_flush(fid)
Flush all pending requests to a netCDF file (PnetCDF only)
module STDIO
Definition: scale_stdio.F90:12
module FILE I/O (netcdf)
module grid index
logical, public io_nml
output log or not? (for namelist, this process)
Definition: scale_stdio.F90:62
integer, public ia
of whole cells: x, local, with HALO
subroutine, public topo_setup
Setup.
module COMMUNICATION
Definition: scale_comm.F90:23
module PROCESS
logical, public topo_exist
topography exists?
module profiler
Definition: scale_prof.F90:10
subroutine, public fileio_open(fid, basename)
open a netCDF file for read
module PRECISION
real(rp), dimension(:,:), allocatable, public topo_zsfc
absolute ground height [m]
module TOPOGRAPHY
subroutine, public fileio_close(fid)
Close a netCDF file.
integer, public io_fid_conf
Config file ID.
Definition: scale_stdio.F90:55
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
integer, public io_fid_nml
Log file ID (only for output namelist)
Definition: scale_stdio.F90:57
integer, public ja
of whole cells: y, local, with HALO