SCALE-RM
scale_file_cartesC.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
10 #include "scalelib.h"
12  !-----------------------------------------------------------------------------
13  !
14  !++ used modules
15  !
16  use scale_precision
17  use scale_io
18  use scale_prof
23  use scale_file_h, only: &
25  !-----------------------------------------------------------------------------
26  implicit none
27  private
28  !-----------------------------------------------------------------------------
29  !
30  !++ Public procedure
31  !
32  public :: file_cartesc_setup
33  public :: file_cartesc_cleanup
39  public :: file_cartesc_check_coordinates
40 
41  public :: file_cartesc_get_size
42  public :: file_cartesc_create
43  public :: file_cartesc_open
45  public :: file_cartesc_def_var
46  public :: file_cartesc_enddef
47  public :: file_cartesc_write_var
48  public :: file_cartesc_read
49  public :: file_cartesc_write
50  public :: file_cartesc_flush
51  public :: file_cartesc_close
52 
53  interface file_cartesc_check_coordinates
54  module procedure file_cartesc_check_coordinates_name
55  module procedure file_cartesc_check_coordinates_id
56  end interface file_cartesc_check_coordinates
57 
58  interface file_cartesc_get_size
59  module procedure file_cartesc_get_size_id
60  module procedure file_cartesc_get_size_name
61  end interface file_cartesc_get_size
62 
63  interface file_cartesc_read
64  module procedure file_cartesc_read_1d
65  module procedure file_cartesc_read_2d
66  module procedure file_cartesc_read_3d
67  module procedure file_cartesc_read_4d
68  module procedure file_cartesc_read_var_1d
69  module procedure file_cartesc_read_var_2d
70  module procedure file_cartesc_read_var_3d
71  module procedure file_cartesc_read_var_4d
72  module procedure file_cartesc_read_auto_2d
73  module procedure file_cartesc_read_auto_3d
74  end interface file_cartesc_read
75 
76  interface file_cartesc_write
77  module procedure file_cartesc_write_1d
78  module procedure file_cartesc_write_2d
79  module procedure file_cartesc_write_3d
80  module procedure file_cartesc_write_3d_t
81  module procedure file_cartesc_write_4d
82  end interface file_cartesc_write
83 
84  interface file_cartesc_write_var
85  module procedure file_cartesc_write_var_1d
86  module procedure file_cartesc_write_var_2d
87  module procedure file_cartesc_write_var_3d
88  module procedure file_cartesc_write_var_3d_t
89  module procedure file_cartesc_write_var_4d
90  end interface file_cartesc_write_var
91 
92  !-----------------------------------------------------------------------------
93  !
94  !++ Public parameters & variables
95  !
96  type, public :: axisattinfo
97  integer :: size_global (1)
98  integer :: start_global(1)
99  integer :: halo_global (2)
100  integer :: halo_local (2)
101  logical :: periodic
102  end type axisattinfo
103 
104  !-----------------------------------------------------------------------------
105  !
106  !++ Private procedure
107  !
108  private :: closeall
109  private :: check_1d
110  private :: check_2d
111  private :: check_3d
112 
113  !-----------------------------------------------------------------------------
114  !
115  !++ Private parameters & variables
116  !
117  real(rp), private :: file_cartesc_datacheck_criteria
118 
119  type dims
120  character(len=H_SHORT) :: name
121  integer :: ndims
122  character(len=H_SHORT) :: dims(3)
123  integer :: size
124  logical :: mapping
125  character(len=H_SHORT) :: area
126  character(len=H_SHORT) :: area_x
127  character(len=H_SHORT) :: area_y
128  character(len=H_SHORT) :: volume
129  character(len=H_SHORT) :: location
130  character(len=H_SHORT) :: grid
131  end type dims
132  integer, parameter :: file_cartesc_ndims = 44
133  type(dims) :: file_cartesc_dims(file_cartesc_ndims)
134 
135  type(axisattinfo) :: file_cartesc_axis_info(4) ! x, xh, y, yh
136 
137 
138  real(rp), private, allocatable :: axis_hgt (:,:,:)
139  real(rp), private, allocatable :: axis_hgtwxy(:,:,:)
140 
141  real(rp), private, allocatable :: axis_lon (:,:) ! [deg]
142  real(rp), private, allocatable :: axis_lonuy(:,:) ! [deg]
143  real(rp), private, allocatable :: axis_lonxv(:,:) ! [deg]
144  real(rp), private, allocatable :: axis_lonuv(:,:) ! [deg]
145  real(rp), private, allocatable :: axis_lat (:,:) ! [deg]
146  real(rp), private, allocatable :: axis_latuy(:,:) ! [deg]
147  real(rp), private, allocatable :: axis_latxv(:,:) ! [deg]
148  real(rp), private, allocatable :: axis_latuv(:,:) ! [deg]
149 
150  real(rp), private, allocatable :: axis_topo (:,:)
151  real(rp), private, allocatable :: axis_lsmask(:,:)
152 
153  real(rp), private, allocatable :: axis_area (:,:)
154  real(rp), private, allocatable :: axis_areazuy_x(:,:,:)
155  real(rp), private, allocatable :: axis_areazxv_y(:,:,:)
156  real(rp), private, allocatable :: axis_areawuy_x(:,:,:)
157  real(rp), private, allocatable :: axis_areawxv_y(:,:,:)
158  real(rp), private, allocatable :: axis_areauy (:,:)
159  real(rp), private, allocatable :: axis_areazxy_x(:,:,:)
160  real(rp), private, allocatable :: axis_areazuv_y(:,:,:)
161  real(rp), private, allocatable :: axis_areaxv (:,:)
162  real(rp), private, allocatable :: axis_areazuv_x(:,:,:)
163  real(rp), private, allocatable :: axis_areazxy_y(:,:,:)
164 
165  real(rp), private, allocatable :: axis_vol (:,:,:)
166  real(rp), private, allocatable :: axis_volwxy(:,:,:)
167  real(rp), private, allocatable :: axis_volzuy(:,:,:)
168  real(rp), private, allocatable :: axis_volzxv(:,:,:)
169 
170  real(rp), private, allocatable :: axis_volo(:,:,:)
171  real(rp), private, allocatable :: axis_voll(:,:,:)
172  real(rp), private, allocatable :: axis_volu(:,:,:)
173 
174  logical, private :: file_axes_written(0:file_file_max-1) ! whether axes have been written
175  ! ! fid starts from zero so index should start from zero
176  logical, private :: file_haszcoord (0:file_file_max-1) ! z-coordinates exist?
177  integer(8), private :: write_buf_amount (0:file_file_max-1) ! sum of write buffer amounts
178 
179  ! global star and count
180  integer, private, target :: startxy (3), countxy (3)
181  integer, private, target :: startzx (2), countzx (2)
182  integer, private, target :: startzxy (4), countzxy (4)
183  integer, private, target :: startzhxy (4), countzhxy (4)
184  integer, private, target :: startocean(4), countocean(4)
185  integer, private, target :: startland (4), countland (4)
186  integer, private, target :: starturban(4), counturban(4)
187  ! local start and end
188  integer, private :: isb2, ieb2, jsb2, jeb2
189 
190  ! MPI element datatype for restart variables
191  integer, private :: etype
192 
193  ! MPI derived datatypes
194  integer, private :: centertypexy
195  integer, private :: centertypezx
196  integer, private :: centertypezxy
197  integer, private :: centertypezhxy
198  integer, private :: centertypeocean
199  integer, private :: centertypeland
200  integer, private :: centertypeurban
201 
202  logical, private :: set_coordinates = .false.
203 
204  !-----------------------------------------------------------------------------
205 contains
206  !-----------------------------------------------------------------------------
208  subroutine file_cartesc_setup
209  use scale_prc, only: &
210  prc_myrank, &
211  prc_abort
212  use scale_prc_cartesc, only: &
213  prc_2drank, &
214  prc_num_x, &
215  prc_num_y
216  use scale_file, only: &
217  file_setup
218  implicit none
219 
220  namelist / param_file_cartesc / &
221  file_cartesc_datacheck_criteria
222 
223  integer :: im, jm
224  integer :: ierr
225  !---------------------------------------------------------------------------
226 
227  call file_setup( prc_myrank )
228 
229 
230  log_newline
231  log_info("FILE_CARTESC_setup",*) 'Setup'
232 
233  file_cartesc_datacheck_criteria = 0.1_rp**(rp)
234 
235  !--- read namelist
236  rewind(io_fid_conf)
237  read(io_fid_conf,nml=param_file_cartesc,iostat=ierr)
238  if( ierr < 0 ) then !--- missing
239  log_info("FILE_CARTESC_setup",*) 'Not found namelist. Default used.'
240  elseif( ierr > 0 ) then !--- fatal error
241  log_error("FILE_CARTESC_setup",*) 'Not appropriate names in namelist PARAM_FILE_CARTESC. Check!'
242  call prc_abort
243  endif
244  log_nml(param_file_cartesc)
245 
246  log_newline
247  log_info("FILE_CARTESC_setup",*) 'NetCDF header information '
248  log_info_cont(*) 'Data source : ', trim(h_source)
249  log_info_cont(*) 'Institute : ', trim(h_institute)
250 
251  log_newline
252  log_info("FILE_CARTESC_setup",*) 'Data consistency criteria : ', &
253  '(file-internal)/internal = ', file_cartesc_datacheck_criteria
254 
255  ! construct indices independent from PRC_PERIODIC_X/Y
256  isb2 = is
257  if( prc_2drank(prc_myrank,1) == 0 ) isb2 = 1
258  ieb2 = ie
259  if( prc_2drank(prc_myrank,1) == prc_num_x-1 ) ieb2 = ia
260 
261  jsb2 = js
262  if( prc_2drank(prc_myrank,2) == 0 ) jsb2 = 1
263  jeb2 = je
264  if( prc_2drank(prc_myrank,2) == prc_num_y-1 ) jeb2 = ja
265 
266  im = ieb2 - isb2 + 1
267  jm = jeb2 - jsb2 + 1
268  allocate( axis_hgt(kmax ,im,jm) )
269  allocate( axis_hgtwxy(kmax+1,im,jm) )
270 
271  allocate( axis_lon(im,jm) )
272  allocate( axis_lonuy(im,jm) )
273  allocate( axis_lonxv(im,jm) )
274  allocate( axis_lonuv(im,jm) )
275  allocate( axis_lat(im,jm) )
276  allocate( axis_latuy(im,jm) )
277  allocate( axis_latxv(im,jm) )
278  allocate( axis_latuv(im,jm) )
279 
280  allocate( axis_topo(im,jm) )
281  allocate( axis_lsmask(im,jm) )
282 
283  allocate( axis_area( im,jm) )
284  allocate( axis_areazuy_x(kmax, im,jm) )
285  allocate( axis_areazxv_y(kmax, im,jm) )
286  allocate( axis_areawuy_x(kmax+1,im,jm) )
287  allocate( axis_areawxv_y(kmax+1,im,jm) )
288  allocate( axis_areauy( im,jm) )
289  allocate( axis_areazxy_x(kmax, im,jm) )
290  allocate( axis_areazuv_y(kmax, im,jm) )
291  allocate( axis_areaxv( im,jm) )
292  allocate( axis_areazuv_x(kmax, im,jm) )
293  allocate( axis_areazxy_y(kmax, im,jm) )
294 
295  allocate( axis_vol(kmax ,im,jm) )
296  allocate( axis_volwxy(kmax+1,im,jm) )
297  allocate( axis_volzuy(kmax ,im,jm) )
298  allocate( axis_volzxv(kmax ,im,jm) )
299 
300  allocate( axis_volo(okmax,im,jm) )
301  allocate( axis_voll(lkmax,im,jm) )
302  allocate( axis_volu(ukmax,im,jm) )
303 
305 
306  write_buf_amount(:) = 0
307 
308  return
309  end subroutine file_cartesc_setup
310 
311  !-----------------------------------------------------------------------------
313  subroutine file_cartesc_cleanup
314  implicit none
315  !---------------------------------------------------------------------------
316 
317  deallocate( axis_hgt )
318  deallocate( axis_hgtwxy )
319 
320  deallocate( axis_lon )
321  deallocate( axis_lonuy )
322  deallocate( axis_lonxv )
323  deallocate( axis_lonuv )
324  deallocate( axis_lat )
325  deallocate( axis_latuy )
326  deallocate( axis_latxv )
327  deallocate( axis_latuv )
328 
329  deallocate( axis_topo )
330  deallocate( axis_lsmask )
331 
332  deallocate( axis_area )
333  deallocate( axis_areazuy_x )
334  deallocate( axis_areazxv_y )
335  deallocate( axis_areawuy_x )
336  deallocate( axis_areawxv_y )
337  deallocate( axis_areauy )
338  deallocate( axis_areazxy_x )
339  deallocate( axis_areazuv_y )
340  deallocate( axis_areaxv )
341  deallocate( axis_areazuv_x )
342  deallocate( axis_areazxy_y )
343 
344  deallocate( axis_vol )
345  deallocate( axis_volwxy )
346  deallocate( axis_volzuy )
347  deallocate( axis_volzxv )
348 
349  deallocate( axis_volo )
350  deallocate( axis_voll )
351  deallocate( axis_volu )
352 
354 
355  call closeall
356 
357  return
358  end subroutine file_cartesc_cleanup
359 
360  !-----------------------------------------------------------------------------
364  !-----------------------------------------------------------------------------
365  subroutine file_cartesc_get_size_name( &
366  basename, &
367  KMAX, OKMAX, LKMAX, UKMAX, &
368  IMAXG, JMAXG, &
369  KHALO, IHALO, JHALO, &
370  aggregate )
371  use scale_file, only: &
372  file_open
373  character(len=*), intent(in) :: basename
374 
375  integer, intent(out) :: kmax, okmax, lkmax, ukmax
376  integer, intent(out) :: imaxg, jmaxg
377  integer, intent(out) :: khalo, ihalo, jhalo
378 
379  logical, intent(in), optional :: aggregate
380 
381  integer :: fid
382 
383  call file_open( basename, & ! (in)
384  fid, & ! (out)
385  aggregate=aggregate ) ! (in)
386 
387  call file_cartesc_get_size_id( fid, & ! (in)
388  kmax, okmax, lkmax, ukmax, & ! (out)
389  imaxg, jmaxg, & ! (out)
390  khalo, ihalo, jhalo ) ! (out)
391 
392  return
393  end subroutine file_cartesc_get_size_name
394  subroutine file_cartesc_get_size_id( &
395  fid, &
396  KMAX, OKMAX, LKMAX, UKMAX, &
397  IMAXG, JMAXG, &
398  KHALO, IHALO, JHALO )
399  use scale_file, only: &
400  file_get_attribute
401 
402  integer, intent(in) :: fid
403 
404  integer, intent(out) :: KMAX, OKMAX, LKMAX, UKMAX
405  integer, intent(out) :: IMAXG, JMAXG
406  integer, intent(out) :: KHALO, IHALO, JHALO
407 
408  integer :: buf(1)
409  logical :: existed
410 
411  call file_get_attribute( fid, "global", "scale_atmos_grid_cartesC_index_kmax", buf(:) )
412  kmax = buf(1)
413  call file_get_attribute( fid, "global", "scale_ocean_grid_cartesC_index_kmax", buf(:), existed=existed )
414  if ( existed ) then
415  okmax = buf(1)
416  else
417  okmax = -1
418  end if
419  call file_get_attribute( fid, "global", "scale_land_grid_cartesC_index_kmax", buf(:), existed=existed )
420  if ( existed ) then
421  lkmax = buf(1)
422  else
423  lkmax = -1
424  end if
425  call file_get_attribute( fid, "global", "scale_urban_grid_cartesC_index_kmax", buf(:), existed=existed )
426  if ( existed ) then
427  ukmax = buf(1)
428  else
429  ukmax = -1
430  end if
431 
432  call file_get_attribute( fid, "global", "scale_atmos_grid_cartesC_index_imaxg", buf(:) )
433  imaxg = buf(1)
434  call file_get_attribute( fid, "global", "scale_atmos_grid_cartesC_index_jmaxg", buf(:) )
435  jmaxg = buf(1)
436 
437  call file_get_attribute( fid, "global", "scale_atmos_grid_cartesC_index_khalo", buf(:) )
438  khalo = buf(1)
439  call file_get_attribute( fid, "global", "scale_atmos_grid_cartesC_index_ihalo", buf(:) )
440  ihalo = buf(1)
441  call file_get_attribute( fid, "global", "scale_atmos_grid_cartesC_index_jhalo", buf(:) )
442  jhalo = buf(1)
443 
444  return
445  end subroutine file_cartesc_get_size_id
446 
447  !-----------------------------------------------------------------------------
450  CZ, FZ, &
451  LON, LONUY, LONXV, LONUV, &
452  LAT, LATUY, LATXV, LATUV, &
453  TOPO, LSMASK )
454  use scale_const, only: &
455  d2r => const_d2r
456  implicit none
457 
458  real(rp), intent(in) :: cz( ka,ia,ja)
459  real(rp), intent(in) :: fz(0:ka,ia,ja)
460  real(rp), intent(in) :: lon ( ia, ja)
461  real(rp), intent(in) :: lonuy(0:ia, ja)
462  real(rp), intent(in) :: lonxv( ia,0:ja)
463  real(rp), intent(in) :: lonuv(0:ia,0:ja)
464  real(rp), intent(in) :: lat ( ia, ja)
465  real(rp), intent(in) :: latuy(0:ia, ja)
466  real(rp), intent(in) :: latxv( ia,0:ja)
467  real(rp), intent(in) :: latuv(0:ia,0:ja)
468  real(rp), intent(in) :: topo ( ia, ja)
469  real(rp), intent(in) :: lsmask( ia, ja)
470  !---------------------------------------------------------------------------
471 
472  axis_hgt(:,:,:) = cz(ks :ke,isb2:ieb2,jsb2:jeb2)
473  axis_hgtwxy(:,:,:) = fz(ks-1:ke,isb2:ieb2,jsb2:jeb2)
474 
475  axis_lon(:,:) = lon(isb2:ieb2,jsb2:jeb2) / d2r
476  axis_lonuy(:,:) = lonuy(isb2:ieb2,jsb2:jeb2) / d2r
477  axis_lonxv(:,:) = lonxv(isb2:ieb2,jsb2:jeb2) / d2r
478  axis_lonuv(:,:) = lonuv(isb2:ieb2,jsb2:jeb2) / d2r
479  axis_lat(:,:) = lat(isb2:ieb2,jsb2:jeb2) / d2r
480  axis_latuy(:,:) = latuy(isb2:ieb2,jsb2:jeb2) / d2r
481  axis_latxv(:,:) = latxv(isb2:ieb2,jsb2:jeb2) / d2r
482  axis_latuv(:,:) = latuv(isb2:ieb2,jsb2:jeb2) / d2r
483 
484  axis_topo(:,:) = topo(isb2:ieb2,jsb2:jeb2)
485  axis_lsmask(:,:) = lsmask(isb2:ieb2,jsb2:jeb2)
486 
487  set_coordinates = .true.
488 
489  return
491 
492  !-----------------------------------------------------------------------------
494  subroutine file_cartesc_set_areavol_atmos( &
495  AREA, AREAZUY_X, AREAZXV_Y, &
496  AREAWUY_X, AREAWXV_Y, &
497  AREAUY, AREAZXY_X, AREAZUV_Y, &
498  AREAXV, AREAZUV_X, AREAZXY_Y, &
499  VOL, VOLWXY, VOLZUY, VOLZXV )
500  use scale_const, only: &
501  d2r => const_d2r
502  implicit none
503  real(rp), intent(in) :: area ( ia,ja)
504  real(rp), intent(in) :: areazuy_x( ka,ia,ja)
505  real(rp), intent(in) :: areazxv_y( ka,ia,ja)
506  real(rp), intent(in) :: areawuy_x(0:ka,ia,ja)
507  real(rp), intent(in) :: areawxv_y(0:ka,ia,ja)
508  real(rp), intent(in) :: areauy ( ia,ja)
509  real(rp), intent(in) :: areazxy_x( ka,ia,ja)
510  real(rp), intent(in) :: areazuv_y( ka,ia,ja)
511  real(rp), intent(in) :: areaxv ( ia,ja)
512  real(rp), intent(in) :: areazuv_x( ka,ia,ja)
513  real(rp), intent(in) :: areazxy_y( ka,ia,ja)
514  real(rp), intent(in) :: vol ( ka,ia,ja)
515  real(rp), intent(in) :: volwxy(0:ka,ia,ja)
516  real(rp), intent(in) :: volzuy( ka,ia,ja)
517  real(rp), intent(in) :: volzxv( ka,ia,ja)
518 
519  axis_area(:,:) = area( isb2:ieb2,jsb2:jeb2)
520  axis_areazuy_x(:,:,:) = areazuy_x(ks :ke,isb2:ieb2,jsb2:jeb2)
521  axis_areazxv_y(:,:,:) = areazxv_y(ks :ke,isb2:ieb2,jsb2:jeb2)
522  axis_areawuy_x(:,:,:) = areawuy_x(ks-1:ke,isb2:ieb2,jsb2:jeb2)
523  axis_areawxv_y(:,:,:) = areawxv_y(ks-1:ke,isb2:ieb2,jsb2:jeb2)
524  axis_areauy(:,:) = areauy( isb2:ieb2,jsb2:jeb2)
525  axis_areazxy_x(:,:,:) = areazxy_x(ks :ke,isb2:ieb2,jsb2:jeb2)
526  axis_areazuv_y(:,:,:) = areazuv_y(ks :ke,isb2:ieb2,jsb2:jeb2)
527  axis_areaxv(:,:) = areaxv( isb2:ieb2,jsb2:jeb2)
528  axis_areazuv_x(:,:,:) = areazuv_x(ks :ke,isb2:ieb2,jsb2:jeb2)
529  axis_areazxy_y(:,:,:) = areazxy_y(ks :ke,isb2:ieb2,jsb2:jeb2)
530 
531  axis_vol(:,:,:) = vol(ks :ke,isb2:ieb2,jsb2:jeb2)
532  axis_volwxy(:,:,:) = volwxy(ks-1:ke,isb2:ieb2,jsb2:jeb2)
533  axis_volzuy(:,:,:) = volzuy(ks :ke,isb2:ieb2,jsb2:jeb2)
534  axis_volzxv(:,:,:) = volzxv(ks :ke,isb2:ieb2,jsb2:jeb2)
535 
536  return
537  end subroutine file_cartesc_set_areavol_atmos
538 
539  !-----------------------------------------------------------------------------
542  VOL )
543  implicit none
544 
545  real(rp), intent(in) :: vol(oka,oia,oja)
546  !---------------------------------------------------------------------------
547 
548  axis_volo(:,:,:) = vol(oks:oke,isb2:ieb2,jsb2:jeb2)
549 
550  return
552 
553  !-----------------------------------------------------------------------------
556  VOL )
557  implicit none
558 
559  real(rp), intent(in) :: vol(lka,lia,lja)
560  !---------------------------------------------------------------------------
561 
562  axis_voll(:,:,:) = vol(lks:lke,isb2:ieb2,jsb2:jeb2)
563 
564  return
565  end subroutine file_cartesc_set_coordinates_land
566 
567  !-----------------------------------------------------------------------------
570  VOL )
571  implicit none
572 
573  real(rp), intent(in) :: vol(uka,uia,uja)
574  !---------------------------------------------------------------------------
575 
576  axis_volu(:,:,:) = vol(uks:uke,isb2:ieb2,jsb2:jeb2)
577 
578  return
580 
581  !-----------------------------------------------------------------------------
583  subroutine file_cartesc_check_coordinates_name( &
584  basename, &
585  atmos, ocean, land, urban, &
586  transpose )
587  implicit none
588 
589  character(len=*), intent(in) :: basename
590  logical, intent(in), optional :: atmos
591  logical, intent(in), optional :: ocean
592  logical, intent(in), optional :: land
593  logical, intent(in), optional :: urban
594  logical, intent(in), optional :: transpose
595 
596  logical :: atmos_
597  logical :: ocean_
598  logical :: land_
599  logical :: urban_
600  logical :: transpose_
601 
602  integer :: fid
603  !---------------------------------------------------------------------------
604 
605  atmos_ = .false.
606  ocean_ = .false.
607  land_ = .false.
608  urban_ = .false.
609  transpose_ = .false.
610 
611  if( present(atmos) ) atmos_ = atmos
612  if( present(ocean) ) ocean_ = ocean
613  if( present(land ) ) land_ = land
614  if( present(urban) ) urban_ = urban
615  if( present(transpose) ) transpose_ = transpose
616 
617  call file_cartesc_open( basename, fid )
618 
619 
620  call file_cartesc_check_coordinates_id( fid, & ! [IN]
621  atmos_, ocean_, land_, urban_, & ! [IN]
622  transpose_ ) ! [IN]
623 
624  return
625  end subroutine file_cartesc_check_coordinates_name
626 
627  !-----------------------------------------------------------------------------
629  subroutine file_cartesc_check_coordinates_id( &
630  fid, &
631  atmos, ocean, land, urban, &
632  transpose )
633  use scale_atmos_grid_cartesc, only: &
637  use scale_ocean_grid_cartesc, only: &
639  use scale_land_grid_cartesc, only: &
641  use scale_urban_grid_cartesc, only: &
643  implicit none
644 
645  integer, intent(in) :: fid
646  logical, intent(in), optional :: atmos
647  logical, intent(in), optional :: ocean
648  logical, intent(in), optional :: land
649  logical, intent(in), optional :: urban
650  logical, intent(in), optional :: transpose
651 
652  logical :: atmos_
653  logical :: ocean_
654  logical :: land_
655  logical :: urban_
656  logical :: transpose_
657 
658  real(rp) :: buffer_z (ka)
659  real(rp) :: buffer_x (ia)
660  real(rp) :: buffer_y (ja)
661  real(rp) :: buffer_xy (ia,ja)
662  real(rp) :: buffer_zxy(ka,ia,ja)
663  real(rp) :: buffer_o (okmax)
664  real(rp) :: buffer_l (lkmax)
665  real(rp) :: buffer_u (ukmax)
666 
667  integer :: xsb, xeb, ysb, yeb
668  !---------------------------------------------------------------------------
669 
670  log_newline
671  log_info("FILE_CARTESC_check_coordinates_id",*) 'Check consistency of axis '
672 
673  atmos_ = .false.
674  ocean_ = .false.
675  land_ = .false.
676  urban_ = .false.
677  transpose_ = .false.
678 
679  if( present(atmos) ) atmos_ = atmos
680  if( present(ocean) ) ocean_ = ocean
681  if( present(land ) ) land_ = land
682  if( present(urban) ) urban_ = urban
683  if( present(transpose) ) transpose_ = transpose
684 
685 
686  xsb = isb - isb2 + 1
687  xeb = ieb - isb + xsb
688  ysb = jsb - jsb2 + 1
689  yeb = jeb - jsb + ysb
690 
691  call file_cartesc_read_var_1d( fid, 'x', 'X', buffer_x(:) )
692  call file_cartesc_read_var_1d( fid, 'y', 'Y', buffer_y(:) )
693  call file_cartesc_flush( fid ) ! for non-blocking I/O
694  call check_1d( atmos_grid_cartesc_cx(isb:ieb), buffer_x(isb:ieb), 'x' )
695  call check_1d( atmos_grid_cartesc_cy(jsb:jeb), buffer_y(jsb:jeb), 'y' )
696 
697  if ( set_coordinates ) then
698  call file_cartesc_read_var_2d( fid, 'lon', 'XY', buffer_xy(:,:) )
699  call file_cartesc_flush( fid ) ! for non-blocking I/O
700  call check_2d( axis_lon(xsb:xeb,ysb:yeb), buffer_xy(isb:ieb,jsb:jeb), 'lon' )
701 
702  call file_cartesc_read_var_2d( fid, 'lat', 'XY', buffer_xy(:,:) )
703  call file_cartesc_flush( fid ) ! for non-blocking I/O
704  call check_2d( axis_lat(xsb:xeb,ysb:yeb), buffer_xy(isb:ieb,jsb:jeb), 'lat' )
705  endif
706 
707  if ( atmos_ ) then
708  call file_cartesc_read_var_1d( fid, 'z', 'Z', buffer_z(:) )
709  if ( .not. transpose_ ) then
710  call file_cartesc_read_var_3d( fid, 'height', 'ZXY', buffer_zxy(:,:,:) )
711  endif
712  call file_cartesc_flush( fid ) ! for non-blocking I/O
713  call check_1d( atmos_grid_cartesc_cz(ks:ke), buffer_z(ks:ke), 'z' )
714  if ( .not. transpose_ ) then
715  call check_3d( axis_hgt(:,xsb:xeb,ysb:yeb), buffer_zxy(ks:ke,isb:ieb,jsb:jeb), 'height', transpose_ )
716  endif
717  endif
718 
719  if ( ocean_ ) then
720  call file_cartesc_read_var_1d( fid, 'oz', 'OZ', buffer_o(:) )
721  call file_cartesc_flush( fid ) ! for non-blocking I/O
722  call check_1d( ocean_grid_cartesc_cz(oks:oke), buffer_o(oks:oke), 'oz' )
723  endif
724 
725  if ( land_ ) then
726  call file_cartesc_read_var_1d( fid, 'lz', 'LZ', buffer_l(:) )
727  call file_cartesc_flush( fid ) ! for non-blocking I/O
728  call check_1d( land_grid_cartesc_cz(lks:lke), buffer_l(lks:lke), 'lz' )
729  endif
730 
731  if ( urban_ ) then
732  call file_cartesc_read_var_1d( fid, 'uz', 'UZ', buffer_u(:) )
733  call file_cartesc_flush( fid ) ! for non-blocking I/O
734  call check_1d( urban_grid_cartesc_cz(uks:uke), buffer_u(uks:uke), 'uz' )
735  endif
736 
737  return
738  end subroutine file_cartesc_check_coordinates_id
739 
740  !-----------------------------------------------------------------------------
742  subroutine file_cartesc_open( &
743  basename, &
744  fid, &
745  aggregate )
746  use scale_file_h, only: &
747  file_fread
748  use scale_file, only: &
749  file_aggregate, &
750  file_open
751  use scale_prc, only: &
752  prc_myrank
753  implicit none
754 
755  character(len=*), intent(in) :: basename
756  integer, intent(out) :: fid
757  logical, intent(in), optional :: aggregate
758  !---------------------------------------------------------------------------
759 
760  call prof_rapstart('FILE_O_NetCDF', 2)
761 
762  call file_open( basename, & ! [IN]
763  fid, & ! [OUT]
764  aggregate=aggregate, & ! [IN]
765  rankid=prc_myrank ) ! [IN]
766 
767  call prof_rapend ('FILE_O_NetCDF', 2)
768 
769  return
770  end subroutine file_cartesc_open
771 
772  !-----------------------------------------------------------------------------
774  subroutine file_cartesc_create( &
775  basename, title, datatype, &
776  fid, &
777  date, subsec, &
778  haszcoord, &
779  append, aggregate, single )
780  use scale_file_h, only: &
781  file_real8, &
782  file_real4
783  use scale_file, only: &
784  file_aggregate, &
785  file_create, &
787  use scale_calendar, only: &
789  use scale_prc, only: &
790  prc_myrank, &
791  prc_abort
792  use scale_time, only: &
793  nowdate => time_nowdate, &
794  nowsubsec => time_nowsubsec
795  use scale_prc_cartesc, only: &
796  prc_2drank, &
797  prc_num_x, &
798  prc_num_y, &
799  prc_periodic_x, &
801  implicit none
802 
803  character(len=*), intent(in) :: basename
804  character(len=*), intent(in) :: title
805  character(len=*), intent(in) :: datatype
806  integer, intent(out) :: fid
807  integer, intent(in), optional :: date(6)
808  real(dp), intent(in), optional :: subsec
809  logical, intent(in), optional :: append
810  logical, intent(in), optional :: haszcoord
811  logical, intent(in), optional :: aggregate
812  logical, intent(in), optional :: single
813 
814  integer :: dtype
815  logical :: append_sw
816  character(len=34) :: tunits
817  character(len=H_SHORT) :: calendar
818  real(dp) :: subsec_
819  integer :: rank_x, rank_y
820  integer :: num_x, num_y
821  logical :: fileexisted
822  logical :: aggregate_
823  logical :: single_
824  integer :: date_(6)
825  !---------------------------------------------------------------------------
826 
827  call prof_rapstart('FILE_O_NetCDF', 2)
828 
829  if ( present(single) ) then
830  single_ = single
831  else
832  single_ = .false.
833  end if
834 
835  ! dtype is used to define the data type of axis variables in file
836  if ( datatype == 'REAL8' ) then
837  dtype = file_real8
838  elseif( datatype == 'REAL4' ) then
839  dtype = file_real4
840  else
841  if ( rp == 8 ) then
842  dtype = file_real8
843  elseif( rp == 4 ) then
844  dtype = file_real4
845  else
846  log_error("FILE_CARTESC_create",*) 'unsupported data type. Check!', trim(datatype)
847  call prc_abort
848  endif
849  endif
850 
851  append_sw = .false.
852  if ( present(append) ) then
853  append_sw = append
854  endif
855 
856  ! create a netCDF file if not already existed. Otherwise, open it.
857  if ( present(date) ) then
858  date_(:) = date(:)
859  else
860  date_(:) = nowdate(:)
861  end if
862  if ( date_(1) > 0 ) then
863  call file_get_cftunits( date_(:), tunits )
864  call calendar_get_name( calendar )
865  else
866  tunits = 'seconds'
867  calendar = ''
868  endif
869 
870 
871  ! check to use PnetCDF I/O
872  if ( present(aggregate) ) then
873  aggregate_ = aggregate
874  else
875  aggregate_ = file_aggregate
876  endif
877 
878  call file_create( basename, & ! [IN]
879  title, & ! [IN]
880  h_source, & ! [IN]
881  h_institute, & ! [IN]
882  fid, & ! [OUT]
883  fileexisted, & ! [OUT]
884  rankid = prc_myrank, & ! [IN]
885  single = single_, & ! [IN]
886  aggregate = aggregate_, & ! [IN]
887  time_units = tunits, & ! [IN]
888  calendar = calendar, & ! [IN]
889  append = append_sw ) ! [IN]
890 
891 
892  if ( fid > 0 .and. (.not. fileexisted) ) then ! do below only once when file is created
893 
894  file_axes_written(fid) = .false. ! indicating axes have not been written yet
895 
896  if ( present( haszcoord ) ) then
897  file_haszcoord(fid) = haszcoord
898  else
899  file_haszcoord(fid) = .true.
900  endif
901 
902  if ( aggregate_ ) then
903  rank_x = 0
904  rank_y = 0
905  num_x = 1
906  num_y = 1
907  else
908  rank_x = prc_2drank(prc_myrank,1)
909  rank_y = prc_2drank(prc_myrank,2)
910  num_x = prc_num_x
911  num_y = prc_num_y
912  end if
913 
914  if ( present( subsec ) ) then
915  subsec_ = subsec
916  else
917  subsec_= nowsubsec
918  end if
919 
920  call file_cartesc_put_globalattributes( fid, & ! [IN]
921  rank_x, rank_y, & ! [IN]
922  num_x, num_y, & ! [IN]
923  prc_periodic_x, prc_periodic_y, & ! [IN]
924  kmax, okmax, lkmax, ukmax, & ! [IN]
925  imaxg, jmaxg, & ! [IN]
926  khalo, ihalo, jhalo, & ! [IN]
927  subsec_, tunits, calendar ) ! [IN]
928 
929  call file_cartesc_def_axes( fid, & ! [IN]
930  dtype, & ! [IN]
931  file_haszcoord(fid) ) ! [IN]
932 
933  end if
934 
935  call prof_rapend ('FILE_O_NetCDF', 2)
936 
937  return
938  end subroutine file_cartesc_create
939 
940  !-----------------------------------------------------------------------------
942  subroutine file_cartesc_enddef( fid )
943  use scale_file, only: &
945  file_opened, &
946  file_single, &
947  file_enddef, &
948  file_flush, &
950  implicit none
951 
952  integer, intent(in) :: fid
953 
954  integer :: start(3)
955  !---------------------------------------------------------------------------
956 
957  if ( .not. file_opened(fid) ) return
958 
959  call prof_rapstart('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
960 
961  call file_enddef( fid ) ! [IN]
962 
963  ! If this enddef is called the first time, write axis variables
964  if ( .NOT. file_axes_written(fid) ) then
965 
966  if ( file_get_aggregate(fid) ) then
967  start(1) = 1
968  start(2) = isga
969  start(3) = jsga
970  else
971  start(1) = 1
972  start(2) = 1
973  start(3) = 1
974  endif
975 
976  call file_cartesc_write_axes( fid, & ! [IN]
977  file_haszcoord(fid), & ! [IN]
978  start(:) ) ! [IN]
979 
980  ! Tell PnetCDF library to use a buffer of size write_buf_amount to aggregate write requests to be post in FILE_CARTESC_write_var
981  if ( file_get_aggregate(fid) ) then
982  call file_flush( fid )
983  call file_attach_buffer( fid, write_buf_amount(fid) )
984  endif
985 
986  file_axes_written(fid) = .true.
987  endif
988 
989  call prof_rapend('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
990 
991  return
992  end subroutine file_cartesc_enddef
993 
994  !-----------------------------------------------------------------------------
996  subroutine file_cartesc_flush( fid )
997  use scale_file, only: &
999  file_opened, &
1000  file_single, &
1001  file_flush
1002  implicit none
1003 
1004  integer, intent(in) :: fid
1005  !---------------------------------------------------------------------------
1006 
1007  if ( .not. file_opened(fid) ) return
1008 
1009  call prof_rapstart('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
1010 
1011  if ( file_get_aggregate(fid) ) then
1012  call file_flush( fid ) ! flush all pending read/write requests
1013  end if
1014 
1015  call prof_rapend('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
1016 
1017  return
1018  end subroutine file_cartesc_flush
1019 
1020  !-----------------------------------------------------------------------------
1022  subroutine file_cartesc_close( fid )
1023  use scale_file, only: &
1025  file_opened, &
1026  file_single, &
1027  file_close, &
1028  file_flush, &
1030  implicit none
1031 
1032  integer, intent(in) :: fid
1033  !---------------------------------------------------------------------------
1034 
1035  if ( .not. file_opened(fid) ) return
1036 
1037  call prof_rapstart('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
1038 
1039  if ( file_get_aggregate(fid) ) then
1040  call file_flush( fid ) ! flush all pending read/write requests
1041  if ( write_buf_amount(fid) > 0 ) then
1042  call file_detach_buffer( fid ) ! detach PnetCDF aggregation buffer
1043  write_buf_amount(fid) = 0 ! reset write request amount
1044  endif
1045  endif
1046 
1047  call file_close( fid ) ! [IN]
1048 
1049  call prof_rapend('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
1050 
1051  return
1052  end subroutine file_cartesc_close
1053 
1054  !-----------------------------------------------------------------------------
1059  !-----------------------------------------------------------------------------
1060  subroutine file_cartesc_read_1d( &
1061  basename, varname, &
1062  dim_type, &
1063  var, &
1064  step, &
1065  aggregate, &
1066  allow_missing )
1067  implicit none
1068  character(len=*), intent(in) :: basename
1069  character(len=*), intent(in) :: varname
1070  character(len=*), intent(in) :: dim_type
1071 
1072  real(RP), intent(out) :: var(:)
1073 
1074  integer, intent(in), optional :: step
1075  logical, intent(in), optional :: aggregate
1076  logical, intent(in), optional :: allow_missing
1077 
1078  integer :: fid
1079  !---------------------------------------------------------------------------
1080 
1081  call file_cartesc_open( basename, & ! [IN]
1082  fid, & ! [OUT]
1083  aggregate=aggregate ) ! [IN]
1084 
1085  call file_cartesc_read_var_1d( fid, varname, dim_type, & ! [IN]
1086  var(:), & ! [OUT]
1087  step=step, & ! [IN]
1088  allow_missing=allow_missing ) ! [IN]
1089 
1090  call file_cartesc_close( fid )
1091 
1092  return
1093  end subroutine file_cartesc_read_1d
1094 
1095  !-----------------------------------------------------------------------------
1097  subroutine file_cartesc_read_2d( &
1098  basename, varname, &
1099  dim_type, &
1100  var, &
1101  step, &
1102  aggregate, &
1103  allow_missing )
1104  implicit none
1105  character(len=*), intent(in) :: basename
1106  character(len=*), intent(in) :: varname
1107  character(len=*), intent(in) :: dim_type
1108 
1109  real(RP), intent(out) :: var(:,:)
1110 
1111  integer, intent(in), optional :: step
1112  logical, intent(in), optional :: aggregate
1113  logical, intent(in), optional :: allow_missing
1114 
1115  integer :: fid
1116  !---------------------------------------------------------------------------
1117 
1118  call file_cartesc_open( basename, & ! [IN]
1119  fid, & ! [OUT]
1120  aggregate=aggregate ) ! [IN]
1121 
1122  call file_cartesc_read_var_2d( fid, varname, dim_type, & ! [IN]
1123  var(:,:), & ! [OUT]
1124  step=step, & ! [IN]
1125  allow_missing=allow_missing ) ! [IN]
1126 
1127  call file_cartesc_close( fid )
1128 
1129  return
1130  end subroutine file_cartesc_read_2d
1131 
1132  !-----------------------------------------------------------------------------
1134  subroutine file_cartesc_read_3d( &
1135  basename, varname, &
1136  dim_type, &
1137  var, &
1138  step, &
1139  aggregate, &
1140  allow_missing )
1141  implicit none
1142  character(len=*), intent(in) :: basename
1143  character(len=*), intent(in) :: varname
1144  character(len=*), intent(in) :: dim_type
1145 
1146  real(RP), intent(out) :: var(:,:,:)
1147 
1148  integer, intent(in), optional :: step
1149  logical, intent(in), optional :: aggregate
1150  logical, intent(in), optional :: allow_missing
1151 
1152  integer :: fid
1153  !---------------------------------------------------------------------------
1154 
1155  call file_cartesc_open( basename, & ! [IN]
1156  fid, & ! [OUT]
1157  aggregate=aggregate ) ! [IN]
1158 
1159  call file_cartesc_read_var_3d( fid, varname, dim_type, & ! [IN]
1160  var(:,:,:), & ! [OUT]
1161  step=step, & ! [IN]
1162  allow_missing=allow_missing ) ! [IN]
1163 
1164  call file_cartesc_close( fid )
1165 
1166  return
1167  end subroutine file_cartesc_read_3d
1168 
1169  !-----------------------------------------------------------------------------
1171  subroutine file_cartesc_read_4d( &
1172  basename, varname, &
1173  dim_type, step, &
1174  var, &
1175  aggregate, &
1176  allow_missing )
1177  implicit none
1178  character(len=*), intent(in) :: basename
1179  character(len=*), intent(in) :: varname
1180  character(len=*), intent(in) :: dim_type
1181  integer, intent(in) :: step
1182 
1183  real(RP), intent(out) :: var(:,:,:,:)
1184 
1185  logical, intent(in), optional :: aggregate
1186  logical, intent(in), optional :: allow_missing
1187 
1188  integer :: fid
1189  !---------------------------------------------------------------------------
1190 
1191  call file_cartesc_open( basename, & ! [IN]
1192  fid, & ! [OUT]
1193  aggregate=aggregate ) ! [IN]
1194 
1195  call file_cartesc_read_var_4d( fid, varname, dim_type, step, & ! [IN]
1196  var(:,:,:,:), & ! [OUT]
1197  allow_missing=allow_missing ) ! [IN]
1198 
1199  call file_cartesc_close( fid )
1200 
1201  return
1202  end subroutine file_cartesc_read_4d
1203 
1204  !-----------------------------------------------------------------------------
1206  subroutine file_cartesc_read_var_1d( &
1207  fid, varname, &
1208  dim_type, &
1209  var, &
1210  step, &
1211  allow_missing )
1212  use scale_file, only: &
1214  file_opened, &
1215  file_single, &
1216  file_read
1217  use scale_prc, only: &
1218  prc_abort
1219  use scale_prc_cartesc, only: &
1220  prc_num_x, &
1221  prc_num_y
1222  use mpi
1223  implicit none
1224  integer, intent(in) :: fid
1225  character(len=*), intent(in) :: varname
1226  character(len=*), intent(in) :: dim_type
1227 
1228  real(RP), intent(out) :: var(:)
1229 
1230  integer, intent(in), optional :: step
1231  logical, intent(in), optional :: allow_missing
1232 
1233  integer :: vsize
1234  integer :: dim1_S, dim1_E
1235  integer :: start(1) ! start offset of globale variable
1236  integer :: count(1) ! request length to the global variable
1237  !---------------------------------------------------------------------------
1238 
1239  if ( .not. file_opened(fid) ) return
1240 
1241  call prof_rapstart('FILE_I_NetCDF', 2, disable_barrier = file_single(fid) )
1242 
1243  log_info("FILE_CARTESC_read_var_1D",'(1x,2A)') 'Read from file (1D), name : ', trim(varname)
1244 
1245  if ( file_get_aggregate(fid) ) then
1246  ! read data and halos into the local buffer
1247  if ( dim_type == 'Z' ) then
1248  vsize = ka
1249  dim1_s = ks
1250  dim1_e = ke
1251  start(1) = 1
1252  elseif( dim_type == 'OZ' ) then
1253  vsize = oka
1254  dim1_s = oks
1255  dim1_e = oke
1256  start(1) = 1
1257  elseif( dim_type == 'LZ' ) then
1258  vsize = lka
1259  dim1_s = lks
1260  dim1_e = lke
1261  start(1) = 1
1262  elseif( dim_type == 'UZ' ) then
1263  vsize = uka
1264  dim1_s = uks
1265  dim1_e = uke
1266  start(1) = 1
1267  elseif( dim_type == 'X' .OR. dim_type == 'CX' ) then
1268  vsize = ia
1269  dim1_s = 1
1270  dim1_e = ia
1271  start(1) = is_ing - ihalo
1272  elseif( dim_type == 'Y' .OR. dim_type == 'CY' ) then
1273  vsize = ja
1274  dim1_s = 1
1275  dim1_e = ja
1276  start(1) = js_ing - jhalo
1277  else
1278  log_error("FILE_CARTESC_read_var_1D",*) 'unsupported dimension type. Check! dim_type:', trim(dim_type), ', item:',trim(varname)
1279  call prc_abort
1280  endif
1281 
1282  if ( size(var) .ne. vsize ) then
1283  log_error("FILE_CARTESC_read_var_1D",*) 'size of var is invalid: ', trim(varname), size(var), vsize
1284  call prc_abort
1285  end if
1286  count(1) = dim1_e - dim1_s + 1
1287  call file_read( fid, varname, & ! (in)
1288  var(dim1_s:dim1_e), & ! (out)
1289  step=step, allow_missing=allow_missing, & ! (in)
1290  ntypes=count(1), dtype=etype, start=start, count=count ) ! (in)
1291 
1292  else
1293  if ( dim_type == 'Z' ) then
1294  vsize = ka
1295  dim1_s = ks
1296  dim1_e = ke
1297  elseif( dim_type == 'OZ' ) then
1298  vsize = oka
1299  dim1_s = oks
1300  dim1_e = oke
1301  elseif( dim_type == 'LZ' ) then
1302  vsize = lka
1303  dim1_s = lks
1304  dim1_e = lke
1305  elseif( dim_type == 'UZ' ) then
1306  vsize = uka
1307  dim1_s = uks
1308  dim1_e = uke
1309  elseif( dim_type == 'X' ) then
1310  vsize = ia
1311  dim1_s = isb
1312  dim1_e = ieb
1313  elseif( dim_type == 'CX' ) then
1314  vsize = ia
1315  dim1_s = 1
1316  dim1_e = ia
1317  elseif( dim_type == 'Y' ) then
1318  vsize = ja
1319  dim1_s = jsb
1320  dim1_e = jeb
1321  elseif( dim_type == 'CY' ) then
1322  vsize = ja
1323  dim1_s = 1
1324  dim1_e = ja
1325  else
1326  log_error("FILE_CARTESC_read_var_1D",*) 'unsupported dimension type. Check! dim_type:', trim(dim_type), ', item:',trim(varname)
1327  call prc_abort
1328  endif
1329 
1330  if ( size(var) .ne. vsize ) then
1331  log_error("FILE_CARTESC_read_var_1D",*) 'size of var is invalid: ', trim(varname), size(var), vsize
1332  call prc_abort
1333  end if
1334  call file_read( fid, varname, var(dim1_s:dim1_e), step=step )
1335  endif
1336 
1337  call prof_rapend('FILE_I_NetCDF', 2, disable_barrier = file_single(fid) )
1338 
1339  return
1340  end subroutine file_cartesc_read_var_1d
1341 
1342  !-----------------------------------------------------------------------------
1344  subroutine file_cartesc_read_var_2d( &
1345  fid, varname, &
1346  dim_type, &
1347  var, &
1348  step, &
1349  allow_missing )
1350  use scale_file, only: &
1352  file_opened, &
1353  file_single, &
1354  file_read
1355  use scale_prc, only: &
1356  prc_abort
1357  implicit none
1358  integer, intent(in) :: fid
1359  character(len=*), intent(in) :: varname
1360  character(len=*), intent(in) :: dim_type
1361 
1362  real(RP), intent(out) :: var(:,:)
1363 
1364  integer, intent(in), optional :: step
1365  logical, intent(in), optional :: allow_missing
1366 
1367  integer :: vsize
1368  integer :: ntypes, dtype
1369  integer, pointer :: start(:), count(:)
1370  integer :: dim1_S, dim1_E
1371  integer :: dim2_S, dim2_E
1372  !---------------------------------------------------------------------------
1373 
1374  if ( .not. file_opened(fid) ) return
1375 
1376  call prof_rapstart('FILE_I_NetCDF', 2, disable_barrier = file_single(fid) )
1377 
1378  log_info("FILE_CARTESC_read_var_2D",'(1x,2A)') 'Read from file (2D), name : ', trim(varname)
1379 
1380  if ( file_get_aggregate(fid) ) then
1381 
1382  ! read data and halos into the local buffer
1383  if ( dim_type == 'XY' ) then
1384  vsize = ia * ja
1385  ntypes = ia * ja
1386  dtype = etype
1387  start => startxy
1388  count => countxy
1389  elseif( dim_type == 'ZX' ) then
1390  ! Because KHALO is not saved in files, we use centerTypeZX, an MPI
1391  ! derived datatype to describe the layout of local read buffer
1392  vsize = ka * ia
1393  ntypes = 1
1394  dtype = centertypezx
1395  start => startzx
1396  count => countzx
1397  else
1398  log_error("FILE_CARTESC_read_var_2D",*) 'unsupported dimension type. Check! dim_type:', trim(dim_type), ', item:',trim(varname)
1399  call prc_abort
1400  endif
1401 
1402  if ( size(var) .ne. vsize ) then
1403  log_error("FILE_CARTESC_read_var_2D",*) 'size of var is invalid: ', trim(varname), size(var), vsize
1404  call prc_abort
1405  end if
1406  call file_read( fid, varname, & ! (in)
1407  var(:,:), & ! (out)
1408  step=step, allow_missing=allow_missing, & ! (in)
1409  ntypes=ntypes, dtype=dtype, start=start, count=count ) ! (in)
1410 
1411  else
1412 
1413  if ( dim_type == 'XY' ) then
1414  vsize = ia * ja
1415  dim1_s = isb
1416  dim1_e = ieb
1417  dim2_s = jsb
1418  dim2_e = jeb
1419  elseif( dim_type == 'ZX' ) then
1420  vsize = ka * ia
1421  dim1_s = ks
1422  dim1_e = ke
1423  dim2_s = isb
1424  dim2_e = ieb
1425  else
1426  log_error("FILE_CARTESC_read_var_2D",*) 'unsupported dimension type. Check! dim_type:', trim(dim_type), ', item:',trim(varname)
1427  call prc_abort
1428  endif
1429 
1430  if ( size(var) .ne. vsize ) then
1431  log_error("FILE_CARTESC_read_var_2D",*) 'size of var is invalid: ', trim(varname), size(var), vsize
1432  call prc_abort
1433  end if
1434  call file_read( fid, varname, var(dim1_s:dim1_e,dim2_s:dim2_e), step=step )
1435  endif
1436 
1437  call prof_rapend('FILE_I_NetCDF', 2, disable_barrier = file_single(fid) )
1438 
1439  return
1440  end subroutine file_cartesc_read_var_2d
1441 
1442  !-----------------------------------------------------------------------------
1444  subroutine file_cartesc_read_var_3d( &
1445  fid, varname, &
1446  dim_type, &
1447  var, &
1448  step, &
1449  allow_missing )
1450  use scale_file, only: &
1452  file_opened, &
1453  file_single, &
1454  file_read
1455  use scale_prc, only: &
1456  prc_abort
1457  use scale_prc_cartesc, only: &
1458  prc_num_x, &
1459  prc_num_y
1460  implicit none
1461  integer, intent(in) :: fid
1462  character(len=*), intent(in) :: varname
1463  character(len=*), intent(in) :: dim_type
1464 
1465  real(RP), intent(out) :: var(:,:,:)
1466 
1467  integer, intent(in), optional :: step
1468  logical, intent(in), optional :: allow_missing
1469 
1470  integer :: vsize
1471  integer :: ntypes, dtype
1472  integer, pointer :: start(:), count(:)
1473  integer :: dim1_S, dim1_E
1474  integer :: dim2_S, dim2_E
1475  integer :: dim3_S, dim3_E
1476  !---------------------------------------------------------------------------
1477 
1478  if ( .not. file_opened(fid) ) return
1479 
1480  call prof_rapstart('FILE_I_NetCDF', 2, disable_barrier = file_single(fid) )
1481 
1482  log_info("FILE_CARTESC_read_var_3D",'(1x,2A)') 'Read from file (3D), name : ', trim(varname)
1483 
1484  if ( file_get_aggregate(fid) ) then
1485 
1486  ! read data and halos into the local buffer
1487  ! Because KHALO is not saved in files, we use mpi derived datatypes to
1488  ! describe the layout of local read buffer
1489  if( dim_type == 'ZXY' &
1490  .or. dim_type == 'ZXHY' &
1491  .or. dim_type == 'ZXYH' ) then
1492  vsize = ka * ia * ja
1493  ntypes = 1
1494  dtype = centertypezxy
1495  start => startzxy
1496  count => countzxy
1497  elseif( dim_type == 'ZHXY' ) then
1498  vsize = ka * ia * ja
1499  ntypes = 1
1500  dtype = centertypezhxy
1501  start => startzhxy
1502  count => countzhxy
1503  elseif( dim_type == 'XYT' ) then
1504  if ( .not. present(step) ) then
1505  log_error("FILE_CARTESC_read_var_3D",*) 'step is necessary for "XYT"'
1506  call prc_abort
1507  end if
1508  vsize = ia * ja * step
1509  ntypes = ia * ja * step
1510  dtype = etype
1511  startxy(3) = 1
1512  countxy(3) = step
1513  start => startxy
1514  count => countxy
1515  elseif( dim_type == 'OXY' ) then
1516  vsize = oka * oia * oja
1517  ntypes = 1
1518  dtype = centertypeocean
1519  start => startocean
1520  count => countocean
1521  elseif( dim_type == 'LXY' ) then
1522  vsize = lka * lia * lja
1523  ntypes = 1
1524  dtype = centertypeland
1525  start => startland
1526  count => countland
1527  elseif( dim_type == 'UXY' ) then
1528  vsize = uka * uia * uja
1529  ntypes = 1
1530  dtype = centertypeurban
1531  start => starturban
1532  count => counturban
1533  else
1534  log_error("FILE_CARTESC_read_var_3D",*) 'unsupported dimension type. Check! dim_type:', trim(dim_type), ', item:',trim(varname)
1535  call prc_abort
1536  endif
1537 
1538  if ( size(var) .ne. vsize ) then
1539  log_error("FILE_CARTESC_read_var_3D",*) 'size of var is invalid: ', trim(varname), size(var), vsize
1540  call prc_abort
1541  end if
1542  call file_read( fid, varname, & ! (in)
1543  var(:,:,:), & ! (out)
1544  step=step, allow_missing=allow_missing, & ! (in)
1545  ntypes=ntypes, dtype=dtype, start=start, count=count ) ! (in)
1546 
1547  else
1548  if( dim_type == 'ZXY' &
1549  .or. dim_type == 'ZXHY' &
1550  .or. dim_type == 'ZXYH' ) then
1551  vsize = ka * ia * ja
1552  dim1_s = ks
1553  dim1_e = ke
1554  dim2_s = isb
1555  dim2_e = ieb
1556  dim3_s = jsb
1557  dim3_e = jeb
1558  elseif( dim_type == 'ZHXY' ) then
1559  vsize = ka * ia * ja
1560  dim1_s = ks-1
1561  dim1_e = ke
1562  dim2_s = isb
1563  dim2_e = ieb
1564  dim3_s = jsb
1565  dim3_e = jeb
1566  elseif( dim_type == 'XYT' ) then
1567  if ( .not. present(step) ) then
1568  log_error("FILE_CARTESC_read_var_3D",*) 'step is necessary for "XYT"'
1569  call prc_abort
1570  end if
1571  vsize = ia * ja * step
1572  dim1_s = isb
1573  dim1_e = ieb
1574  dim2_s = jsb
1575  dim2_e = jeb
1576  dim3_s = 1
1577  dim3_e = step
1578  elseif( dim_type == 'OXY' ) then
1579  vsize = oka * oia * oja
1580  dim1_s = oks
1581  dim1_e = oke
1582  dim2_s = isb
1583  dim2_e = ieb
1584  dim3_s = jsb
1585  dim3_e = jeb
1586  elseif( dim_type == 'LXY' ) then
1587  vsize = lka * lia * lja
1588  dim1_s = lks
1589  dim1_e = lke
1590  dim2_s = isb
1591  dim2_e = ieb
1592  dim3_s = jsb
1593  dim3_e = jeb
1594  elseif( dim_type == 'UXY' ) then
1595  vsize = uka * uia * uja
1596  dim1_s = uks
1597  dim1_e = uke
1598  dim2_s = isb
1599  dim2_e = ieb
1600  dim3_s = jsb
1601  dim3_e = jeb
1602  else
1603  log_error("FILE_CARTESC_read_var_3D",*) 'unsupported dimension type. Check! dim_type:', trim(dim_type), ', item:',trim(varname)
1604  call prc_abort
1605  endif
1606 
1607  if ( size(var) .ne. vsize ) then
1608  log_error("FILE_CARTESC_read_var_3D",*) 'size of var is invalid: ', trim(varname), size(var), vsize
1609  call prc_abort
1610  end if
1611  call file_read( fid, varname, var(dim1_s:dim1_e,dim2_s:dim2_e,dim3_s:dim3_e), &
1612  step=step, allow_missing=allow_missing )
1613 
1614  endif
1615 
1616  call prof_rapend('FILE_I_NetCDF', 2, disable_barrier = file_single(fid) )
1617 
1618  return
1619  end subroutine file_cartesc_read_var_3d
1620 
1621  !-----------------------------------------------------------------------------
1623  subroutine file_cartesc_read_var_4d( &
1624  fid, varname, &
1625  dim_type, &
1626  step, &
1627  var, &
1628  allow_missing )
1629  use scale_file, only: &
1631  file_opened, &
1632  file_single, &
1633  file_read
1634  use scale_prc, only: &
1635  prc_abort
1636  use scale_prc_cartesc, only: &
1637  prc_num_x, &
1638  prc_num_y
1639  implicit none
1640  integer, intent(in) :: fid
1641  character(len=*), intent(in) :: varname
1642  character(len=*), intent(in) :: dim_type
1643  integer, intent(in) :: step
1644 
1645  real(RP), intent(out) :: var(:,:,:,:)
1646 
1647  logical, intent(in), optional :: allow_missing
1648 
1649  integer :: vsize
1650  integer :: dtype
1651  integer, pointer :: start(:), count(:)
1652  integer :: dim1_S, dim1_E
1653  integer :: dim2_S, dim2_E
1654  integer :: dim3_S, dim3_E
1655  integer :: dim4_S, dim4_E
1656  !---------------------------------------------------------------------------
1657 
1658  if ( .not. file_opened(fid) ) return
1659 
1660  call prof_rapstart('FILE_I_NetCDF', 2, disable_barrier = file_single(fid) )
1661 
1662  log_info("FILE_CARTESC_read_var_4D",'(1x,2A)') 'Read from file (4D), name : ', trim(varname)
1663 
1664  if ( file_get_aggregate(fid) ) then
1665  ! read data and halos into the local buffer
1666  if ( dim_type == 'ZXYT' &
1667  .or. dim_type == 'ZXHYT' &
1668  .or. dim_type == 'ZXYHT' ) then
1669  vsize = ka * ia * ja * step
1670  dtype = centertypezxy
1671  start => startzxy
1672  count => countzxy
1673  elseif ( dim_type == 'ZHXYT' ) then
1674  vsize = ka * ia * ja * step
1675  dtype = centertypezhxy
1676  start => startzhxy
1677  count => countzhxy
1678  elseif ( dim_type == 'OXYT' ) then
1679  vsize = oka * oia * oja * step
1680  dtype = centertypeocean
1681  start => startocean
1682  count => countocean
1683  elseif ( dim_type == 'LXYT' ) then
1684  vsize = lka * lia * lja * step
1685  dtype = centertypeland
1686  start => startland
1687  count => countland
1688  elseif ( dim_type == 'LXYT' ) then
1689  vsize = lka * lia * lja * step
1690  dtype = centertypeland
1691  start => startland
1692  count => countland
1693  elseif ( dim_type == 'UXYT' ) then
1694  vsize = uka * uia * uja * step
1695  dtype = centertypeurban
1696  start => starturban
1697  count => counturban
1698  else
1699  log_error("FILE_CARTESC_read_var_4D",*) 'unsupported dimension type. Check! dim_type:', trim(dim_type), ', item:',trim(varname)
1700  call prc_abort
1701  endif
1702 
1703  if ( size(var) .ne. vsize ) then
1704  log_error("FILE_CARTESC_read_var_4D",*) 'size of var is invalid: ', trim(varname), size(var), vsize
1705  call prc_abort
1706  end if
1707  start(4) = 1
1708  count(4) = step
1709  call file_read( fid, varname, & ! (in)
1710  var(:,:,:,:), & ! (out)
1711  allow_missing=allow_missing, & ! (in)
1712  ntypes=step, dtype=dtype, start=start, count=count ) ! (in)
1713 
1714  else
1715  if ( dim_type == 'ZXYT' &
1716  .or. dim_type == 'ZXHYT' &
1717  .or. dim_type == 'ZXYHT' ) then
1718  vsize = ka * ia * ja * step
1719  dim1_s = ks
1720  dim1_e = ke
1721  dim2_s = isb
1722  dim2_e = ieb
1723  dim3_s = jsb
1724  dim3_e = jeb
1725  elseif ( dim_type == 'ZHXYT' ) then
1726  vsize = ka * ia * ja * step
1727  dim1_s = ks-1
1728  dim1_e = ke
1729  dim2_s = isb
1730  dim2_e = ieb
1731  dim3_s = jsb
1732  dim3_e = jeb
1733  elseif ( dim_type == 'OXYT' ) then
1734  vsize = oka * oia * oja * step
1735  dim1_s = oks
1736  dim1_e = oke
1737  dim2_s = isb
1738  dim2_e = ieb
1739  dim3_s = jsb
1740  dim3_e = jeb
1741  elseif ( dim_type == 'LXYT' ) then
1742  vsize = lka * lia * lja * step
1743  dim1_s = lks
1744  dim1_e = lke
1745  dim2_s = isb
1746  dim2_e = ieb
1747  dim3_s = jsb
1748  dim3_e = jeb
1749  elseif ( dim_type == 'OXYT' ) then
1750  vsize = lka * lia * lja * step
1751  dim1_s = lks
1752  dim1_e = lke
1753  dim2_s = isb
1754  dim2_e = ieb
1755  dim3_s = jsb
1756  dim3_e = jeb
1757  else
1758  log_error("FILE_CARTESC_read_var_4D",*) 'unsupported dimension type. Check! dim_type:', trim(dim_type), ', item:',trim(varname)
1759  call prc_abort
1760  endif
1761 
1762  if ( size(var) .ne. vsize ) then
1763  log_error("FILE_CARTESC_read_var_4D",*) 'size of var is invalid: ', trim(varname), size(var), vsize
1764  call prc_abort
1765  end if
1766  dim4_s = 1
1767  dim4_e = step
1768  call file_read( fid, varname, & ! (in)
1769  var(dim1_s:dim1_e,dim2_s:dim2_e,dim3_s:dim3_e,dim4_s:dim4_e) ) ! (out)
1770  endif
1771 
1772  call prof_rapend('FILE_I_NetCDF', 2, disable_barrier = file_single(fid) )
1773 
1774  return
1775  end subroutine file_cartesc_read_var_4d
1776 
1777  !-----------------------------------------------------------------------------
1779  subroutine file_cartesc_read_auto_2d( &
1780  fid, varname, &
1781  var, &
1782  step, existed )
1783  use scale_file, only: &
1784  file_opened, &
1785  file_single, &
1786  file_get_shape, &
1787  file_get_datainfo, &
1788  file_get_attribute, &
1789  file_read
1790  use scale_prc, only: &
1791  prc_abort
1792  implicit none
1793  integer, intent(in) :: fid
1794  character(len=*), intent(in) :: varname
1795 
1796  real(RP), intent(out) :: var(:,:)
1797 
1798  integer, intent(in), optional :: step
1799 
1800  logical, intent(out), optional :: existed
1801 
1802  integer :: dims(2)
1803  integer :: halos(2)
1804  integer :: start(2)
1805  integer :: count(2)
1806  character(len=H_SHORT) :: dnames(2)
1807 
1808  integer :: nx, ny
1809  integer :: n
1810 
1811  logical :: existed2
1812 
1813  intrinsic size
1814  !---------------------------------------------------------------------------
1815 
1816  if ( .not. file_opened(fid) ) return
1817 
1818  call prof_rapstart('FILE_I_NetCDF', 2, disable_barrier = file_single(fid) )
1819 
1820  log_info("FILE_CARTESC_read_auto_2D",'(1x,2A)') 'Read from file (2D), name : ', trim(varname)
1821 
1822  call file_get_datainfo( fid, varname, dim_name=dnames(:), existed=existed2 )
1823 
1824  if ( present( existed ) ) then
1825  existed = existed2
1826  if ( .not. existed2 ) return
1827  end if
1828 
1829  if ( .not. existed2 ) then
1830  log_error("FILE_CARTESC_read_auto_2D",*) 'variable not found: ', trim(varname)
1831  call prc_abort
1832  end if
1833 
1834  call file_get_shape( fid, varname, dims(:) )
1835  nx = size(var,1)
1836  ny = size(var,2)
1837 
1838  if ( nx==dims(1) .and. ny==dims(2) ) then
1839  start(:) = (/1,1/)
1840  else
1841  do n = 1, 2
1842  call file_get_attribute( fid, dnames(n), "halo_local", halos(:), existed=existed2 )
1843  if ( existed2 ) then
1844  start(n) = halos(1) + 1
1845  else
1846  start(n) = 1
1847  end if
1848  end do
1849  end if
1850  count(:) = (/nx,ny/)
1851 
1852  call file_read( fid, varname, var(:,:), step=step, start=start(:), count=count(:) )
1853  call file_cartesc_flush( fid )
1854 
1855  call prof_rapend('FILE_I_NetCDF', 2, disable_barrier = file_single(fid) )
1856 
1857  return
1858  end subroutine file_cartesc_read_auto_2d
1859 
1860  !-----------------------------------------------------------------------------
1862  subroutine file_cartesc_read_auto_3d( &
1863  fid, varname, &
1864  var, &
1865  step, existed )
1866  use scale_file, only: &
1867  file_opened, &
1868  file_single, &
1869  file_get_shape, &
1870  file_get_datainfo, &
1871  file_get_attribute, &
1872  file_read
1873  use scale_prc, only: &
1874  prc_abort
1875  implicit none
1876  integer, intent(in) :: fid
1877  character(len=*), intent(in) :: varname
1878 
1879  real(RP), intent(out) :: var(:,:,:)
1880 
1881  integer, intent(in), optional :: step
1882 
1883  logical, intent(out), optional :: existed
1884 
1885  integer :: dims(3)
1886  integer :: halos(3)
1887  integer :: start(3)
1888  integer :: count(3)
1889  character(len=H_SHORT) :: dnames(3)
1890 
1891  logical :: existed2
1892 
1893  real(RP), allocatable :: buf(:,:,:)
1894  integer :: nx, ny, nz
1895  integer :: n
1896  integer :: k, i, j
1897 
1898  intrinsic size
1899  !---------------------------------------------------------------------------
1900 
1901  if ( .not. file_opened(fid) ) return
1902 
1903  call prof_rapstart('FILE_I_NetCDF', 2, disable_barrier = file_single(fid) )
1904 
1905  log_info("FILE_CARTESC_read_auto_3D",'(1x,2A)') 'Read from file (3D), name : ', trim(varname)
1906 
1907  call file_get_datainfo( fid, varname, dim_name=dnames(:), existed=existed2 )
1908 
1909  if ( present(existed) ) then
1910  existed = existed2
1911  if ( .not. existed2 ) return
1912  end if
1913 
1914  if ( .not. existed2 ) then
1915  log_error("FILE_CARTESC_read_auto_3D",*) 'variable not found: ', trim(varname)
1916  call prc_abort
1917  end if
1918 
1919  call file_get_shape( fid, varname, dims(:) )
1920  nz = size(var,1)
1921  nx = size(var,2)
1922  ny = size(var,3)
1923 
1924  if ( ( dnames(1)(1:1)=="z" .or. dnames(1)(2:2)=="z" ) .and. dnames(2)(1:1)=="x" .and. dnames(3)(1:1)=="y" ) then
1925  if ( nz==dims(1) .and. nx==dims(2) .and. ny==dims(3) ) then
1926  start(:) = (/1,1,1/)
1927  else if ( dnames(1)=="zh" .and. nz+1==dims(1) .and. nx==dims(2) .and. ny==dims(3) ) then
1928  start(:) = (/2,1,1/)
1929  else
1930  do n = 1, 3
1931  call file_get_attribute( fid, dnames(n), "halo_local", halos(:), existed=existed2 )
1932  if ( existed2 ) then
1933  start(n) = halos(1) + 1
1934  else if ( dnames(n)=="zh" ) then
1935  start(n) = 2
1936  else
1937  start(n) = 1
1938  end if
1939  end do
1940  end if
1941  count(:) = (/nz,nx,ny/)
1942  call file_read( fid, varname, var(:,:,:), step=step, start=start(:), count=count(:) )
1943  call file_cartesc_flush( fid )
1944  else if ( dnames(1)(1:1)=="x" .and. dnames(2)(1:1)=="y" .and. ( dnames(3)(1:1)=="z" .or. dnames(3)(2:2)=="z" ) ) then
1945  allocate( buf(nx,ny,nz) )
1946  if ( nx==dims(1) .and. ny==dims(2) .and. nz==dims(3) ) then
1947  start(:) = (/1,1,1/)
1948  else if ( nx==dims(1) .and. ny==dims(2) .and. nz+1==dims(3) .and. dnames(3)=="zh" ) then
1949  start(:) = (/1,1,2/)
1950  else
1951  do n = 1, 3
1952  call file_get_attribute( fid, dnames(n), "halo_local", halos(:), existed=existed2 )
1953  if ( existed2 ) then
1954  start(n) = halos(1) + 1
1955  else if ( dnames(n)=="zh" ) then
1956  start(n) = 2
1957  else
1958  start(n) = 1
1959  end if
1960  end do
1961  end if
1962  count(:) = (/nx,ny,nz/)
1963  call file_read( fid, varname, buf(:,:,:), step=step, start=start(:), count=count(:) )
1964  call file_cartesc_flush( fid )
1965 
1966  !$omp parallel do
1967  do j = 1, ny
1968  do i = 1, nx
1969  do k = 1, nz
1970  var(k,i,j) = buf(i,j,k)
1971  end do
1972  end do
1973  end do
1974  deallocate(buf)
1975  else
1976  log_error("FILE_CARTESC_read_auto_3D",*) 'invalid dimension'
1977  call prc_abort
1978  end if
1979 
1980  call prof_rapend('FILE_I_NetCDF', 2, disable_barrier = file_single(fid) )
1981 
1982  return
1983  end subroutine file_cartesc_read_auto_3d
1984 
1985  !-----------------------------------------------------------------------------
1990  !-----------------------------------------------------------------------------
1991  subroutine file_cartesc_write_1d( &
1992  var, &
1993  basename, title, &
1994  varname, desc, unit, &
1995  dim_type, datatype, &
1996  date, subsec, &
1997  append, aggregate, &
1998  standard_name, &
1999  cell_measures )
2000  implicit none
2001 
2002  real(RP), intent(in) :: var(:)
2003  character(len=*), intent(in) :: basename
2004  character(len=*), intent(in) :: title
2005  character(len=*), intent(in) :: varname
2006  character(len=*), intent(in) :: desc
2007  character(len=*), intent(in) :: unit
2008  character(len=*), intent(in) :: dim_type
2009  character(len=*), intent(in) :: datatype
2010 
2011  integer, intent(in), optional :: date(6)
2012  real(DP), intent(in), optional :: subsec
2013  logical, intent(in), optional :: append
2014  logical, intent(in), optional :: aggregate
2015  character(len=*), intent(in), optional :: standard_name
2016  character(len=*), intent(in), optional :: cell_measures
2017 
2018  integer :: fid, vid
2019  !---------------------------------------------------------------------------
2020 
2021  log_info("FILE_CARTESC_write_1D",'(1x,2A)') 'Write to file (1D), name : ', trim(varname)
2022 
2023  call file_cartesc_create( basename, title, datatype, & ! [IN]
2024  fid, & ! [OUT]
2025  date=date, subsec=subsec, & ! [IN]
2026  append=append, aggregate=aggregate, single=.true. ) ! [IN]
2027 
2028  call file_cartesc_def_var( fid, varname, desc, unit, dim_type, datatype, & ! [IN]
2029  vid, & ! [OUT]
2030  standard_name=standard_name, & ! [IN]
2031  cell_measures=cell_measures ) ! [IN]
2032 
2033  call file_cartesc_enddef( fid )
2034 
2035  call file_cartesc_write_var_1d( fid, vid, var, varname, dim_type )
2036 
2037  return
2038  end subroutine file_cartesc_write_1d
2039 
2040  !-----------------------------------------------------------------------------
2042  subroutine file_cartesc_write_2d( &
2043  var, &
2044  basename, title, &
2045  varname, desc, unit, &
2046  dim_type, datatype, &
2047  date, subsec, &
2048  fill_halo, haszcoord, &
2049  append, aggregate, &
2050  standard_name, &
2051  cell_measures )
2052  implicit none
2053 
2054  real(RP), intent(in) :: var(:,:)
2055  character(len=*), intent(in) :: basename
2056  character(len=*), intent(in) :: title
2057  character(len=*), intent(in) :: varname
2058  character(len=*), intent(in) :: desc
2059  character(len=*), intent(in) :: unit
2060  character(len=*), intent(in) :: dim_type
2061  character(len=*), intent(in) :: datatype
2062 
2063  integer, intent(in), optional :: date(6)
2064  real(DP), intent(in), optional :: subsec
2065  logical, intent(in), optional :: fill_halo
2066  logical, intent(in), optional :: haszcoord
2067  logical, intent(in), optional :: append
2068  logical, intent(in), optional :: aggregate
2069  character(len=*), intent(in), optional :: standard_name
2070  character(len=*), intent(in), optional :: cell_measures
2071 
2072  integer :: fid, vid
2073  !---------------------------------------------------------------------------
2074 
2075  log_info("FILE_CARTESC_write_2D",'(1x,2A)') 'Write to file (2D), name : ', trim(varname)
2076 
2077  call file_cartesc_create( basename, title, datatype, & ! [IN]
2078  fid, & ! [OUT]
2079  date=date, subsec=subsec, & ! [IN]
2080  haszcoord=haszcoord, & ! [IN]
2081  append=append, aggregate=aggregate ) ! [IN]
2082 
2083  call file_cartesc_def_var( fid, varname, desc, unit, dim_type, datatype, & ! [IN]
2084  vid, & ! [OUT]
2085  standard_name=standard_name, & ! [IN]
2086  cell_measures=cell_measures ) ! [IN]
2087 
2088  call file_cartesc_enddef( fid )
2089 
2090  call file_cartesc_write_var_2d( fid, vid, var, varname, dim_type, fill_halo )
2091 
2092  return
2093  end subroutine file_cartesc_write_2d
2094 
2095  !-----------------------------------------------------------------------------
2097  subroutine file_cartesc_write_3d( &
2098  var, &
2099  basename, title, &
2100  varname, desc, unit, &
2101  dim_type, datatype, &
2102  date, subsec, &
2103  fill_halo, &
2104  append, aggregate, &
2105  standard_name, &
2106  cell_measures )
2107  implicit none
2108 
2109  real(RP), intent(in) :: var(:,:,:)
2110  character(len=*), intent(in) :: basename
2111  character(len=*), intent(in) :: title
2112  character(len=*), intent(in) :: varname
2113  character(len=*), intent(in) :: desc
2114  character(len=*), intent(in) :: unit
2115  character(len=*), intent(in) :: dim_type
2116  character(len=*), intent(in) :: datatype
2117 
2118  integer, intent(in), optional :: date(6)
2119  real(DP), intent(in), optional :: subsec
2120  logical, intent(in), optional :: fill_halo
2121  logical, intent(in), optional :: append
2122  logical, intent(in), optional :: aggregate
2123  character(len=*), intent(in), optional :: standard_name
2124  character(len=*), intent(in), optional :: cell_measures
2125 
2126  integer :: fid, vid
2127  !---------------------------------------------------------------------------
2128 
2129  log_info("FILE_CARTESC_write_3D",'(1x,2A)') 'Write to file (3D), name : ', trim(varname)
2130 
2131  call file_cartesc_create( basename, title, datatype, & ! [IN]
2132  fid, & ! [OUT]
2133  date=date, subsec=subsec, & ! [IN]
2134  append=append, aggregate=aggregate ) ! [IN]
2135 
2136  call file_cartesc_def_var( fid, varname, desc, unit, dim_type, datatype, & ! [IN]
2137  vid, & ! [OUT]
2138  standard_name=standard_name, & ! [IN]
2139  cell_measures=cell_measures ) ! [IN]
2140 
2141  call file_cartesc_enddef( fid )
2142 
2143  call file_cartesc_write_var_3d( fid, vid, var, varname, dim_type, fill_halo )
2144 
2145 
2146  return
2147  end subroutine file_cartesc_write_3d
2148 
2149  !-----------------------------------------------------------------------------
2151  subroutine file_cartesc_write_3d_t( &
2152  var, &
2153  basename, title, &
2154  varname, desc, unit, &
2155  dim_type, datatype, &
2156  timeintv, tsince, &
2157  timetarg, timeofs, &
2158  fill_halo, &
2159  append, aggregate, &
2160  standard_name, &
2161  cell_measures )
2162  implicit none
2163 
2164  real(RP), intent(in) :: var(:,:,:)
2165  character(len=*), intent(in) :: basename
2166  character(len=*), intent(in) :: title
2167  character(len=*), intent(in) :: varname
2168  character(len=*), intent(in) :: desc
2169  character(len=*), intent(in) :: unit
2170  character(len=*), intent(in) :: dim_type
2171  character(len=*), intent(in) :: datatype
2172  real(DP), intent(in) :: timeintv
2173  integer , intent(in) :: tsince(6)
2174 
2175  integer, intent(in), optional :: timetarg
2176  real(DP), intent(in), optional :: timeofs
2177  logical, intent(in), optional :: fill_halo
2178  logical, intent(in), optional :: append
2179  logical, intent(in), optional :: aggregate
2180  character(len=*), intent(in), optional :: standard_name
2181  character(len=*), intent(in), optional :: cell_measures
2182 
2183  integer :: fid, vid
2184  integer :: nsteps
2185 
2186  intrinsic :: size
2187  !---------------------------------------------------------------------------
2188 
2189  log_info("FILE_CARTESC_write_3D_t",'(1x,3A)') 'Write to file (3D), name : ', trim(varname), 'with time dimension'
2190 
2191  call file_cartesc_create( basename, title, datatype, & ! [IN]
2192  fid, & ! [OUT]
2193  date=tsince, & ! [IN]
2194  append=append, aggregate=aggregate ) ! [IN]
2195 
2196  if ( present(timetarg) ) then
2197  nsteps = 1
2198  else
2199  nsteps = size(var,3)
2200  endif
2201  call file_cartesc_def_var( fid, varname, desc, unit, dim_type, datatype, & ! [IN]
2202  vid, & ! [OUT]
2203  standard_name=standard_name, & ! [IN]
2204  cell_measures=cell_measures, & ! [IN]
2205  timeintv=timeintv, nsteps=nsteps ) ! [IN]
2206 
2207  call file_cartesc_enddef( fid )
2208 
2209  call file_cartesc_write_var_3d_t( fid, vid, var, varname, dim_type, timeintv, &
2210  timetarg, timeofs, fill_halo )
2211 
2212  return
2213  end subroutine file_cartesc_write_3d_t
2214 
2215  !-----------------------------------------------------------------------------
2217  subroutine file_cartesc_write_4d( &
2218  var, &
2219  basename, title, &
2220  varname, desc, unit, &
2221  dim_type, datatype, &
2222  timeintv, tsince, &
2223  timetarg, timeofs, &
2224  fill_halo, &
2225  append, aggregate, &
2226  standard_name, &
2227  cell_measures )
2228  implicit none
2229 
2230  real(RP), intent(in) :: var(:,:,:,:)
2231  character(len=*), intent(in) :: basename
2232  character(len=*), intent(in) :: title
2233  character(len=*), intent(in) :: varname
2234  character(len=*), intent(in) :: desc
2235  character(len=*), intent(in) :: unit
2236  character(len=*), intent(in) :: dim_type
2237  character(len=*), intent(in) :: datatype
2238  real(DP), intent(in) :: timeintv
2239  integer, intent(in) :: tsince(6)
2240 
2241  integer, intent(in), optional :: timetarg
2242  real(DP), intent(in), optional :: timeofs
2243  logical, intent(in), optional :: fill_halo
2244  logical, intent(in), optional :: append
2245  logical, intent(in), optional :: aggregate
2246  character(len=*), intent(in), optional :: standard_name
2247  character(len=*), intent(in), optional :: cell_measures
2248 
2249  integer :: fid, vid
2250  integer :: nsteps
2251 
2252  intrinsic :: size
2253  !---------------------------------------------------------------------------
2254 
2255  log_info("FILE_CARTESC_write_4D",'(1x,2A)') 'Write to file (4D), name : ', trim(varname)
2256 
2257  call file_cartesc_create( basename, title, datatype, & ! [IN]
2258  fid, & ! [OUT]
2259  date=tsince, & ! [IN]
2260  append=append, aggregate=aggregate ) ! [IN]
2261 
2262  if ( present(timetarg) ) then
2263  nsteps = 1
2264  else
2265  nsteps = size(var,3)
2266  endif
2267  call file_cartesc_def_var( fid, varname, desc, unit, dim_type, datatype, & ! [IN]
2268  vid, & ! [OUT]
2269  standard_name=standard_name, & ! [IN]
2270  cell_measures=cell_measures, & ! [IN]
2271  timeintv=timeintv, nsteps=nsteps ) ! [IN]
2272 
2273  call file_cartesc_enddef( fid )
2274 
2275  call file_cartesc_write_var_4d( fid, vid, var, varname, dim_type, timeintv, &
2276  timetarg, timeofs, fill_halo )
2277 
2278  return
2279  end subroutine file_cartesc_write_4d
2280 
2281  !-----------------------------------------------------------------------------
2283  subroutine file_cartesc_put_globalattributes( &
2284  fid, &
2285  prc_rank_x, prc_rank_y, &
2286  prc_num_x, prc_num_y, &
2287  prc_periodic_x, prc_periodic_y, &
2288  kmax, okmax, lkmax, ukmax, &
2289  imaxg, jmaxg, &
2290  khalo, ihalo, jhalo, &
2291  time, tunits, calendar )
2294  use scale_file, only: &
2295  file_opened, &
2296  file_single, &
2297  file_set_attribute
2298 
2299  integer, intent(in) :: fid
2300  integer, intent(in) :: prc_rank_x, prc_rank_y
2301  integer, intent(in) :: prc_num_x, prc_num_y
2302  logical, intent(in) :: prc_periodic_x, prc_periodic_y
2303  integer, intent(in) :: kmax, okmax, lkmax, ukmax
2304  integer, intent(in) :: imaxg, jmaxg
2305  integer, intent(in) :: khalo, ihalo, jhalo
2306  real(dp), intent(in) :: time
2307  character(len=*), intent(in) :: tunits
2308  character(len=*), intent(in) :: calendar
2309  !---------------------------------------------------------------------------
2310 
2311  if ( .not. file_opened(fid) ) return
2312 
2313  call prof_rapstart('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
2314 
2315  call file_set_attribute( fid, "global", "Conventions", "CF-1.6" ) ! [IN]
2316 
2317  call file_set_attribute( fid, "global", "grid_name", atmos_grid_cartesc_name ) ! [IN]
2318 
2319  call file_set_attribute( fid, "global", "scale_cartesC_prc_rank_x", (/prc_rank_x/) ) ! [IN]
2320  call file_set_attribute( fid, "global", "scale_cartesC_prc_rank_y", (/prc_rank_y/) ) ! [IN]
2321 
2322  call file_set_attribute( fid, "global", "scale_cartesC_prc_num_x", (/prc_num_x/) ) ! [IN]
2323  call file_set_attribute( fid, "global", "scale_cartesC_prc_num_y", (/prc_num_y/) ) ! [IN]
2324 
2325  call file_set_attribute( fid, "global", "scale_cartesC_prc_periodic_z", .false. ) ! [IN]
2326  call file_set_attribute( fid, "global", "scale_cartesC_prc_periodic_x", prc_periodic_x ) ! [IN]
2327  call file_set_attribute( fid, "global", "scale_cartesC_prc_periodic_y", prc_periodic_y ) ! [IN]
2328 
2329  call file_set_attribute( fid, "global", "scale_atmos_grid_cartesC_index_imaxg", (/imaxg/) ) ! [IN]
2330  call file_set_attribute( fid, "global", "scale_atmos_grid_cartesC_index_jmaxg", (/jmaxg/) ) ! [IN]
2331 
2332  call file_set_attribute( fid, "global", "scale_atmos_grid_cartesC_index_kmax", (/kmax/) ) ! [IN]
2333  if ( okmax > 0 ) call file_set_attribute( fid, "global", "scale_ocean_grid_cartesC_index_kmax", (/okmax/) ) ! [IN]
2334  if ( lkmax > 0 ) call file_set_attribute( fid, "global", "scale_land_grid_cartesC_index_kmax", (/lkmax/) ) ! [IN]
2335  if ( ukmax > 0 ) call file_set_attribute( fid, "global", "scale_urban_grid_cartesC_index_kmax", (/ukmax/) ) ! [IN]
2336 
2337  call file_set_attribute( fid, "global", "scale_atmos_grid_cartesC_index_khalo", (/khalo/) ) ! [IN]
2338  call file_set_attribute( fid, "global", "scale_atmos_grid_cartesC_index_ihalo", (/ihalo/) ) ! [IN]
2339  call file_set_attribute( fid, "global", "scale_atmos_grid_cartesC_index_jhalo", (/jhalo/) ) ! [IN]
2340 
2341  if ( calendar /= "" ) call file_set_attribute( fid, "global", "calendar", calendar )
2342  call file_set_attribute( fid, "global", "time_units", tunits )
2343  call file_set_attribute( fid, "global", "time_start", (/time/) )
2344 
2345  call prof_rapend('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
2346 
2347  return
2348  end subroutine file_cartesc_put_globalattributes
2349 
2350  !-----------------------------------------------------------------------------
2352  subroutine file_cartesc_def_axes( &
2353  fid, &
2354  dtype, &
2355  hasZ )
2356  use scale_file, only: &
2357  file_opened, &
2358  file_single, &
2360  file_def_axis, &
2361  file_set_attribute, &
2364  use scale_const, only: &
2365  undef => const_undef
2366  use scale_mapprojection, only: &
2368  implicit none
2369 
2370  integer, intent(in) :: fid
2371  integer, intent(in) :: dtype
2372  logical, intent(in) :: hasZ
2373 
2374  integer :: iall ! grid size, x-axis, (whole domain or local tile), including halo
2375  integer :: jall ! grid size, y-axis, (whole domain or local tile), including halo
2376  integer :: isize ! grid size, x-axis, (whole domain or local tile), without halo except domain edge
2377  integer :: jsize ! grid size, y-axis, (whole domain or local tile), without halo except domain edge
2378 
2379  character(len=2) :: axisname(3)
2380 
2381  logical, save :: set_dim = .false.
2382  !---------------------------------------------------------------------------
2383 
2384  if ( .not. file_opened(fid) ) return
2385 
2386  call prof_rapstart('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
2387 
2388  if ( .not. set_dim ) then
2390  set_dim = .true.
2391  end if
2392 
2393  if ( file_get_aggregate(fid) ) then
2394  iall = iag
2395  jall = jag
2396  isize = iag
2397  jsize = jag
2398  else
2399  iall = ia
2400  jall = ja
2401  isize = imaxb
2402  jsize = jmaxb
2403  endif
2404 
2405  if ( hasz ) then
2406  call file_def_axis( fid, 'z' , 'Z' , 'm', 'z' , dtype, kmax, bounds=.true. )
2407  call file_def_axis( fid, 'zh' , 'Z (half level)' , 'm', 'zh' , dtype, kmax+1, bounds=.true. )
2408 
2409  if ( okmax > 0 ) then
2410  call file_def_axis( fid, 'oz' , 'OZ' , 'm', 'oz' , dtype, okmax, bounds=.true. )
2411  call file_def_axis( fid, 'ozh', 'OZ (half level)', 'm', 'ozh', dtype, okmax+1, bounds=.true. )
2412  end if
2413 
2414  if ( lkmax > 0 ) then
2415  call file_def_axis( fid, 'lz' , 'LZ' , 'm', 'lz' , dtype, lkmax, bounds=.true. )
2416  call file_def_axis( fid, 'lzh', 'LZ (half level)', 'm', 'lzh', dtype, lkmax+1, bounds=.true. )
2417  end if
2418 
2419  if ( ukmax > 0 ) then
2420  call file_def_axis( fid, 'uz' , 'UZ' , 'm', 'uz' , dtype, ukmax, bounds=.true. )
2421  call file_def_axis( fid, 'uzh', 'UZ (half level)', 'm', 'uzh', dtype, ukmax+1, bounds=.true. )
2422  end if
2423  end if
2424 
2425  call file_def_axis( fid, 'x' , 'X' , 'm', 'x' , dtype, isize, bounds=.true. )
2426  call file_def_axis( fid, 'xh' , 'X (half level)' , 'm', 'xh' , dtype, isize, bounds=.true. )
2427  call file_def_axis( fid, 'y' , 'Y' , 'm', 'y' , dtype, jsize, bounds=.true. )
2428  call file_def_axis( fid, 'yh' , 'Y (half level)' , 'm', 'yh' , dtype, jsize, bounds=.true. )
2429 
2430  if ( hasz ) then
2431  call file_def_axis( fid, 'CZ' , 'Atmos Grid Center Position Z', 'm', 'CZ', dtype, ka )
2432  call file_def_axis( fid, 'FZ' , 'Atmos Grid Face Position Z', 'm', 'FZ', dtype, ka+1 )
2433  call file_def_axis( fid, 'CDZ' , 'Grid Cell length Z', 'm', 'CZ', dtype, ka )
2434  call file_def_axis( fid, 'FDZ' , 'Grid distance Z', 'm', 'FDZ', dtype, ka-1 )
2435  call file_def_axis( fid, 'CBFZ' , 'Boundary factor Center Z', '1', 'CZ', dtype, ka )
2436  call file_def_axis( fid, 'FBFZ' , 'Boundary factor Face Z', '1', 'FZ', dtype, ka+1 )
2437 
2438  if ( okmax > 0 ) then
2439  call file_def_axis( fid, 'OCZ' , 'Ocean Grid Center Position Z', 'm', 'OCZ', dtype, okmax )
2440  call file_def_axis( fid, 'OFZ' , 'Ocean Grid Face Position Z', 'm', 'OFZ', dtype, okmax+1 )
2441  call file_def_axis( fid, 'OCDZ' , 'Ocean Grid Cell length Z', 'm', 'OCZ', dtype, okmax )
2442  end if
2443 
2444  if ( lkmax > 0 ) then
2445  call file_def_axis( fid, 'LCZ' , 'Land Grid Center Position Z', 'm', 'LCZ', dtype, lkmax )
2446  call file_def_axis( fid, 'LFZ' , 'Land Grid Face Position Z', 'm', 'LFZ', dtype, lkmax+1 )
2447  call file_def_axis( fid, 'LCDZ' , 'Land Grid Cell length Z', 'm', 'LCZ', dtype, lkmax )
2448  end if
2449 
2450  if ( ukmax > 0 ) then
2451  call file_def_axis( fid, 'UCZ' , 'Urban Grid Center Position Z', 'm', 'UCZ', dtype, ukmax )
2452  call file_def_axis( fid, 'UFZ' , 'Urban Grid Face Position Z', 'm', 'UFZ', dtype, ukmax+1 )
2453  call file_def_axis( fid, 'UCDZ' , 'Urban Grid Cell length Z', 'm', 'UCZ', dtype, ukmax )
2454  end if
2455  end if
2456 
2457  call file_def_axis( fid, 'CX' , 'Atmos Grid Center Position X', 'm', 'CX', dtype, iall )
2458  call file_def_axis( fid, 'CY' , 'Atmos Grid Center Position Y', 'm', 'CY', dtype, jall )
2459  call file_def_axis( fid, 'FX' , 'Atmos Grid Face Position X', 'm', 'FX', dtype, iall+1 )
2460  call file_def_axis( fid, 'FY' , 'Atmos Grid Face Position Y', 'm', 'FY', dtype, jall+1 )
2461  call file_def_axis( fid, 'CDX' , 'Grid Cell length X', 'm', 'CX', dtype, iall )
2462  call file_def_axis( fid, 'CDY' , 'Grid Cell length Y', 'm', 'CY', dtype, jall )
2463  call file_def_axis( fid, 'FDX' , 'Grid distance X', 'm', 'FX', dtype, iall+1 )
2464  call file_def_axis( fid, 'FDY' , 'Grid distance Y', 'm', 'FY', dtype, jall+1 )
2465  call file_def_axis( fid, 'CBFX' , 'Boundary factor Center X', '1', 'CX', dtype, iall )
2466  call file_def_axis( fid, 'CBFY' , 'Boundary factor Center Y', '1', 'CY', dtype, jall )
2467  call file_def_axis( fid, 'FBFX' , 'Boundary factor Face X', '1', 'FX', dtype, iall+1 )
2468  call file_def_axis( fid, 'FBFY' , 'Boundary factor Face Y', '1', 'FY', dtype, jall+1 )
2469 
2470  call file_def_axis( fid, 'CXG' , 'Grid Center Position X (global)', 'm', 'CXG', dtype, iag )
2471  call file_def_axis( fid, 'CYG' , 'Grid Center Position Y (global)', 'm', 'CYG', dtype, jag )
2472  call file_def_axis( fid, 'FXG' , 'Grid Face Position X (global)', 'm', 'FXG', dtype, iag+1 )
2473  call file_def_axis( fid, 'FYG' , 'Grid Face Position Y (global)', 'm', 'FYG', dtype, jag+1 )
2474  call file_def_axis( fid, 'CDXG' , 'Grid Cell length X (global)', 'm', 'CXG', dtype, iag )
2475  call file_def_axis( fid, 'CDYG' , 'Grid Cell length Y (global)', 'm', 'CYG', dtype, jag )
2476  call file_def_axis( fid, 'FDXG' , 'Grid distance X (global)', 'm', 'FXG', dtype, iag+1 )
2477  call file_def_axis( fid, 'FDYG' , 'Grid distance Y (global)', 'm', 'FYG', dtype, jag+1 )
2478  call file_def_axis( fid, 'CBFXG', 'Boundary factor Center X (global)', '1', 'CXG', dtype, iag )
2479  call file_def_axis( fid, 'CBFYG', 'Boundary factor Center Y (global)', '1', 'CYG', dtype, jag )
2480  call file_def_axis( fid, 'FBFXG', 'Boundary factor Face X (global)', '1', 'FXG', dtype, iag+1 )
2481  call file_def_axis( fid, 'FBFYG', 'Boundary factor Face Y (global)', '1', 'FYG', dtype, jag+1 )
2482 
2483  ! associate coordinates
2484  axisname(1:2) = (/'x ','y '/)
2485  call file_def_associatedcoordinate( fid, 'lon' , 'longitude', 'degrees_east' , axisname(1:2), dtype )
2486  axisname(1:2) = (/'xh','y '/)
2487  call file_def_associatedcoordinate( fid, 'lon_uy', 'longitude (half level uy)', 'degrees_east' , axisname(1:2), dtype )
2488  axisname(1:2) = (/'x ','yh'/)
2489  call file_def_associatedcoordinate( fid, 'lon_xv', 'longitude (half level xv)', 'degrees_east' , axisname(1:2), dtype )
2490  axisname(1:2) = (/'xh','yh'/)
2491  call file_def_associatedcoordinate( fid, 'lon_uv', 'longitude (half level uv)', 'degrees_east' , axisname(1:2), dtype )
2492  axisname(1:2) = (/'x ','y '/)
2493  call file_def_associatedcoordinate( fid, 'lat' , 'latitude', 'degrees_north', axisname(1:2), dtype )
2494  axisname(1:2) = (/'xh','y '/)
2495  call file_def_associatedcoordinate( fid, 'lat_uy', 'latitude (half level uy)', 'degrees_north', axisname(1:2), dtype )
2496  axisname(1:2) = (/'x ','yh'/)
2497  call file_def_associatedcoordinate( fid, 'lat_xv', 'latitude (half level xv)', 'degrees_north', axisname(1:2), dtype )
2498  axisname(1:2) = (/'xh','yh'/)
2499  call file_def_associatedcoordinate( fid, 'lat_uv', 'latitude (half level uv)', 'degrees_north', axisname(1:2), dtype )
2500 
2501  if ( hasz ) then
2502  axisname(1:2) = (/'x ','y '/)
2503  call file_def_associatedcoordinate( fid, 'topo' , 'topography', 'm', axisname(1:2), dtype )
2504  end if
2505  axisname(1:2) = (/'x ','y '/)
2506  call file_def_associatedcoordinate( fid, 'lsmask', 'fraction for land-sea mask', '1', axisname(1:2), dtype )
2507 
2508  axisname(1:2) = (/'x ','y '/)
2509  call file_def_associatedcoordinate( fid, 'cell_area', 'area of grid cell', 'm2', axisname(1:2), dtype )
2510  axisname(1:2) = (/'xh','y '/)
2511  call file_def_associatedcoordinate( fid, 'cell_area_uy', 'area of grid cell (half level uy)', 'm2', axisname(1:2), dtype )
2512  axisname(1:2) = (/'x ','yh'/)
2513  call file_def_associatedcoordinate( fid, 'cell_area_xv', 'area of grid cell (half level xv)', 'm2', axisname(1:2), dtype )
2514  axisname(1:2) = (/'xh','yh'/)
2515 
2516  if ( hasz ) then
2517  axisname = (/'z ', 'x ', 'y '/)
2518  call file_def_associatedcoordinate( fid, 'height', 'height above ground level', &
2519  'm', axisname(1:3), dtype )
2520  axisname = (/'zh', 'x ', 'y '/)
2521  call file_def_associatedcoordinate( fid, 'height_wxy', 'height above ground level (half level wxy)', &
2522  'm', axisname(1:3), dtype )
2523 
2524  axisname = (/'z ', 'xh', 'y '/)
2525  call file_def_associatedcoordinate( fid, 'cell_area_zuy_x', 'area of grid cell face (half level zuy, normal x)', &
2526  'm2', axisname(1:3), dtype )
2527  axisname = (/'z ', 'x ', 'yh'/)
2528  call file_def_associatedcoordinate( fid, 'cell_area_zxv_y', 'area of grid cell face (half level zxv, normal y)', &
2529  'm2', axisname(1:3), dtype )
2530  axisname = (/'zh', 'xh', 'y '/)
2531  call file_def_associatedcoordinate( fid, 'cell_area_wuy_x', 'area of grid cell face (half level wuy, normal x)', &
2532  'm2', axisname(1:3), dtype )
2533  axisname = (/'zh', 'x ', 'yh'/)
2534  call file_def_associatedcoordinate( fid, 'cell_area_wxv_y', 'area of grid cell face (half level wxv, normal y)', &
2535  'm2', axisname(1:3), dtype )
2536  axisname = (/'z ', 'x ', 'y '/)
2537  call file_def_associatedcoordinate( fid, 'cell_area_zxy_x', 'area of grid cell face (half level zxy, normal x)', &
2538  'm2', axisname(1:3), dtype )
2539  axisname = (/'z ', 'xh', 'yh'/)
2540  call file_def_associatedcoordinate( fid, 'cell_area_zuv_y', 'area of grid cell face (half level zuv, normal y)', &
2541  'm2', axisname(1:3), dtype )
2542  axisname = (/'z ', 'xh', 'yh'/)
2543  call file_def_associatedcoordinate( fid, 'cell_area_zuv_x', 'area of grid cell face (half level zuv, normal x)', &
2544  'm2', axisname(1:3), dtype )
2545  axisname = (/'z ', 'x ', 'y '/)
2546  call file_def_associatedcoordinate( fid, 'cell_area_zxy_y', 'area of grid cell face (half level zxy, normal y)', &
2547  'm2', axisname(1:3), dtype )
2548 
2549  axisname = (/'z ', 'x ', 'y '/)
2550  call file_def_associatedcoordinate( fid, 'cell_volume', 'volume of grid cell', &
2551  'm3', axisname(1:3), dtype )
2552  axisname = (/'zh', 'x ', 'y '/)
2553  call file_def_associatedcoordinate( fid, 'cell_volume_wxy', 'volume of grid cell (half level wxy)', &
2554  'm3', axisname(1:3), dtype )
2555  axisname = (/'z ', 'xh', 'y '/)
2556  call file_def_associatedcoordinate( fid, 'cell_volume_zuy', 'volume of grid cell (half level zuy)', &
2557  'm3', axisname(1:3), dtype )
2558  axisname = (/'z ', 'x ', 'yh'/)
2559  call file_def_associatedcoordinate( fid, 'cell_volume_zxv', 'volume of grid cell (half level zxv)', &
2560  'm3', axisname(1:3), dtype )
2561 
2562  if ( okmax > 0 ) then
2563  axisname = (/'oz', 'x ', 'y '/)
2564  call file_def_associatedcoordinate( fid, 'cell_volume_oxy', 'volume of grid cell', &
2565  'm3', axisname(1:3), dtype )
2566  end if
2567  if ( lkmax > 0 ) then
2568  axisname = (/'lz', 'x ', 'y '/)
2569  call file_def_associatedcoordinate( fid, 'cell_volume_lxy', 'volume of grid cell', &
2570  'm3', axisname(1:3), dtype )
2571  end if
2572  if ( ukmax > 0 ) then
2573  axisname = (/'uz', 'x ', 'y '/)
2574  call file_def_associatedcoordinate( fid, 'cell_volume_uxy', 'volume of grid cell', &
2575  'm3', axisname(1:3), dtype )
2576  end if
2577  endif
2578 
2579  ! attributes
2580 
2581  if ( hasz ) then
2582  if ( okmax > 0 ) then
2583  call file_set_attribute( fid, 'oz' , 'positive', 'down' )
2584  call file_set_attribute( fid, 'ozh', 'positive', 'down' )
2585  end if
2586  if ( lkmax > 0 ) then
2587  call file_set_attribute( fid, 'lz' , 'positive', 'down' )
2588  call file_set_attribute( fid, 'lzh', 'positive', 'down' )
2589  end if
2590  if ( ukmax > 0 ) then
2591  call file_set_attribute( fid, 'uz' , 'positive', 'down' )
2592  call file_set_attribute( fid, 'uzh', 'positive', 'down' )
2593  end if
2594  if ( okmax > 0 ) then
2595  call file_set_attribute( fid, 'OCZ', 'positive', 'down' )
2596  call file_set_attribute( fid, 'OFZ', 'positive', 'down' )
2597  end if
2598  if ( lkmax > 0 ) then
2599  call file_set_attribute( fid, 'LCZ', 'positive', 'down' )
2600  call file_set_attribute( fid, 'LFZ', 'positive', 'down' )
2601  end if
2602  if ( ukmax > 0 ) then
2603  call file_set_attribute( fid, 'UCZ', 'positive', 'down' )
2604  call file_set_attribute( fid, 'UFZ', 'positive', 'down' )
2605  end if
2606  endif
2607 
2608  if ( file_get_aggregate(fid) ) then
2609  call file_set_attribute( fid, "x" , "size_global" , (/ iag /) )
2610  call file_set_attribute( fid, "x" , "start_global", (/ 1 /) )
2611  call file_set_attribute( fid, "x" , "halo_global" , (/ ihalo, ihalo /) )
2612  call file_set_attribute( fid, "x" , "halo_local" , (/ ihalo, ihalo /) )
2613 
2614  call file_set_attribute( fid, "xh", "size_global" , (/ iag+1 /) )
2615  call file_set_attribute( fid, "xh", "start_global", (/ 1 /) )
2616  call file_set_attribute( fid, "xh", "halo_global" , (/ ihalo, ihalo /) )
2617  call file_set_attribute( fid, "xh", "halo_local" , (/ ihalo, ihalo /) )
2618 
2619  call file_set_attribute( fid, "y" , "size_global" , (/ jag /) )
2620  call file_set_attribute( fid, "y" , "start_global", (/ 1 /) )
2621  call file_set_attribute( fid, "y" , "halo_global" , (/ jhalo, jhalo /) )
2622  call file_set_attribute( fid, "y" , "halo_local" , (/ jhalo, jhalo /) )
2623 
2624  call file_set_attribute( fid, "yh", "size_global" , (/ jag+1 /) )
2625  call file_set_attribute( fid, "yh", "start_global", (/ 1 /) )
2626  call file_set_attribute( fid, "yh", "halo_global" , (/ jhalo, jhalo /) )
2627  call file_set_attribute( fid, "yh", "halo_local" , (/ jhalo, jhalo /) )
2628  else
2629  call file_set_attribute( fid, "x" , "size_global" , file_cartesc_axis_info(1)%size_global (:) )
2630  call file_set_attribute( fid, "x" , "start_global", file_cartesc_axis_info(1)%start_global(:) )
2631  call file_set_attribute( fid, "x" , "halo_global" , file_cartesc_axis_info(1)%halo_global (:) )
2632  call file_set_attribute( fid, "x" , "halo_local" , file_cartesc_axis_info(1)%halo_local (:) )
2633 
2634  call file_set_attribute( fid, "xh", "size_global" , file_cartesc_axis_info(2)%size_global (:) )
2635  call file_set_attribute( fid, "xh", "start_global", file_cartesc_axis_info(2)%start_global(:) )
2636  call file_set_attribute( fid, "xh", "halo_global" , file_cartesc_axis_info(2)%halo_global (:) )
2637  call file_set_attribute( fid, "xh", "halo_local" , file_cartesc_axis_info(2)%halo_local (:) )
2638 
2639  call file_set_attribute( fid, "y" , "size_global" , file_cartesc_axis_info(3)%size_global (:) )
2640  call file_set_attribute( fid, "y" , "start_global", file_cartesc_axis_info(3)%start_global(:) )
2641  call file_set_attribute( fid, "y" , "halo_global" , file_cartesc_axis_info(3)%halo_global (:) )
2642  call file_set_attribute( fid, "y" , "halo_local" , file_cartesc_axis_info(3)%halo_local (:) )
2643 
2644  call file_set_attribute( fid, "yh", "size_global" , file_cartesc_axis_info(4)%size_global (:) )
2645  call file_set_attribute( fid, "yh", "start_global", file_cartesc_axis_info(4)%start_global(:) )
2646  call file_set_attribute( fid, "yh", "halo_global" , file_cartesc_axis_info(4)%halo_global (:) )
2647  call file_set_attribute( fid, "yh", "halo_local" , file_cartesc_axis_info(4)%halo_local (:) )
2648  end if
2649 
2650  call file_set_attribute( fid, "x" , "periodic" , file_cartesc_axis_info(1)%periodic )
2651  call file_set_attribute( fid, "xh", "periodic" , file_cartesc_axis_info(2)%periodic )
2652  call file_set_attribute( fid, "y" , "periodic" , file_cartesc_axis_info(3)%periodic )
2653  call file_set_attribute( fid, "yh", "periodic" , file_cartesc_axis_info(4)%periodic )
2654 
2655  ! map projection info
2656 
2657  if ( mapprojection_mappinginfo%mapping_name /= "" ) then
2658  call file_set_attribute( fid, "x" , "standard_name", "projection_x_coordinate" )
2659  call file_set_attribute( fid, "xh", "standard_name", "projection_x_coordinate" )
2660  call file_set_attribute( fid, "y" , "standard_name", "projection_y_coordinate" )
2661  call file_set_attribute( fid, "yh", "standard_name", "projection_y_coordinate" )
2662 
2663  call file_add_associatedvariable( fid, mapprojection_mappinginfo%mapping_name )
2664  call file_set_attribute( fid, mapprojection_mappinginfo%mapping_name, "grid_mapping_name", mapprojection_mappinginfo%mapping_name )
2665 
2666  if ( mapprojection_mappinginfo%false_easting /= undef ) then
2667  call file_set_attribute( fid, & ! [IN]
2668  mapprojection_mappinginfo%mapping_name, & ! [IN]
2669  "false_easting", & ! [IN]
2670  mapprojection_mappinginfo%false_easting ) ! [IN]
2671  endif
2672 
2673  if ( mapprojection_mappinginfo%false_northing /= undef ) then
2674  call file_set_attribute( fid, & ! [IN]
2675  mapprojection_mappinginfo%mapping_name, & ! [IN]
2676  "false_northing", & ! [IN]
2677  mapprojection_mappinginfo%false_northing ) ! [IN]
2678  endif
2679 
2680  if ( mapprojection_mappinginfo%longitude_of_central_meridian /= undef ) then
2681  call file_set_attribute( fid, & ! [IN]
2682  mapprojection_mappinginfo%mapping_name, & ! [IN]
2683  "longitude_of_central_meridian", & ! [IN]
2684  mapprojection_mappinginfo%longitude_of_central_meridian ) ! [IN]
2685  endif
2686 
2687  if ( mapprojection_mappinginfo%longitude_of_projection_origin /= undef ) then
2688  call file_set_attribute( fid, & ! [IN]
2689  mapprojection_mappinginfo%mapping_name, & ! [IN]
2690  "longitude_of_projection_origin", & ! [IN]
2691  mapprojection_mappinginfo%longitude_of_projection_origin ) ! [IN]
2692  endif
2693 
2694  if ( mapprojection_mappinginfo%latitude_of_projection_origin /= undef ) then
2695  call file_set_attribute( fid, & ! [IN]
2696  mapprojection_mappinginfo%mapping_name, & ! [IN]
2697  "latitude_of_projection_origin", & ! [IN]
2698  mapprojection_mappinginfo%latitude_of_projection_origin ) ! [IN]
2699  endif
2700 
2701  if ( mapprojection_mappinginfo%straight_vertical_longitude_from_pole /= undef ) then
2702  call file_set_attribute( fid, & ! [IN]
2703  mapprojection_mappinginfo%mapping_name, & ! [IN]
2704  "straight_vertical_longitude_from_pole", & ! [IN]
2705  mapprojection_mappinginfo%straight_vertical_longitude_from_pole ) ! [IN]
2706  endif
2707 
2708  if ( mapprojection_mappinginfo%standard_parallel(1) /= undef ) then
2709  if ( mapprojection_mappinginfo%standard_parallel(2) /= undef ) then
2710  call file_set_attribute( fid, & ! [IN]
2711  mapprojection_mappinginfo%mapping_name, & ! [IN]
2712  "standard_parallel", & ! [IN]
2713  mapprojection_mappinginfo%standard_parallel(:) ) ! [IN]
2714  else
2715  call file_set_attribute( fid, & ! [IN]
2716  mapprojection_mappinginfo%mapping_name, & ! [IN]
2717  "standard_parallel", & ! [IN]
2718  mapprojection_mappinginfo%standard_parallel(1) ) ! [IN]
2719  endif
2720  endif
2721 
2722  if ( mapprojection_mappinginfo%rotation /= undef ) then
2723  call file_set_attribute( fid, & ! [IN]
2724  mapprojection_mappinginfo%mapping_name, & ! [IN]
2725  "rotation", & ! [IN]
2726  mapprojection_mappinginfo%rotation ) ! [IN]
2727  endif
2728 
2729  endif
2730 
2731  ! cell measures
2732 
2733  call file_set_attribute( fid, "cell_area", "standard_name", "area" ) ! [IN]
2734  call file_set_attribute( fid, "cell_area_uy", "standard_name", "area" ) ! [IN]
2735  call file_set_attribute( fid, "cell_area_xv", "standard_name", "area" ) ! [IN]
2736 
2737  if ( hasz ) then
2738  call file_set_attribute( fid, "cell_area_zuy_x", "standard_name", "area" ) ! [IN]
2739  call file_set_attribute( fid, "cell_area_zxv_y", "standard_name", "area" ) ! [IN]
2740  call file_set_attribute( fid, "cell_area_wuy_x", "standard_name", "area" ) ! [IN]
2741  call file_set_attribute( fid, "cell_area_wxv_y", "standard_name", "area" ) ! [IN]
2742  call file_set_attribute( fid, "cell_area_zxy_x", "standard_name", "area" ) ! [IN]
2743  call file_set_attribute( fid, "cell_area_zuv_y", "standard_name", "area" ) ! [IN]
2744  call file_set_attribute( fid, "cell_area_zuv_x", "standard_name", "area" ) ! [IN]
2745  call file_set_attribute( fid, "cell_area_zxy_y", "standard_name", "area" ) ! [IN]
2746 
2747  call file_set_attribute( fid, "cell_volume", "standard_name", "volume" ) ! [IN]
2748  call file_set_attribute( fid, "cell_volume_wxy", "standard_name", "volume" ) ! [IN]
2749  call file_set_attribute( fid, "cell_volume_zuy", "standard_name", "volume" ) ! [IN]
2750  call file_set_attribute( fid, "cell_volume_zxv", "standard_name", "volume" ) ! [IN]
2751 
2752  if ( okmax > 0 ) then
2753  call file_set_attribute( fid, "cell_volume_oxy", "standard_name", "volume" ) ! [IN]
2754  end if
2755  if ( lkmax > 0 ) then
2756  call file_set_attribute( fid, "cell_volume_lxy", "standard_name", "volume" ) ! [IN]
2757  end if
2758  if ( ukmax > 0 ) then
2759  call file_set_attribute( fid, "cell_volume_uxy", "standard_name", "volume" ) ! [IN]
2760  end if
2761  end if
2762 
2763  ! SGRID
2764  call file_add_associatedvariable( fid, "grid" )
2765  call file_set_attribute( fid, "grid", "cf_role", "grid_topology" )
2766  call file_set_attribute( fid, "grid", "topology_dimension", (/ 2 /) )
2767  call file_set_attribute( fid, "grid", "node_dimensions", "xh yh" )
2768  call file_set_attribute( fid, "grid", "face_dimensions", "x: xh (padding: none) y: yh (padding: none)" )
2769  call file_set_attribute( fid, "grid", "node_coordinates", "lon_uv lat_uv" )
2770  call file_set_attribute( fid, "grid", "face_coordinates", "lon lat" )
2771  call file_set_attribute( fid, "grid", "edge1_coordinates", "lon_uy lat_uy" )
2772  call file_set_attribute( fid, "grid", "edge2_coordinates", "lon_xv lat_xv" )
2773  call file_set_attribute( fid, "grid", "vertical_dimensions", "z: zh (padding: none)" )
2774 
2775  if ( okmax > 0 ) then
2776  call file_add_associatedvariable( fid, "grid_ocean" )
2777  call file_set_attribute( fid, "grid_ocean", "cf_role", "grid_topology" )
2778  call file_set_attribute( fid, "grid_ocean", "topology_dimension", (/ 2 /) )
2779  call file_set_attribute( fid, "grid_ocean", "node_dimensions", "xh yh" )
2780  call file_set_attribute( fid, "grid_ocean", "face_dimensions", "x: xh (padding: none) y: yh (padding: none)" )
2781  call file_set_attribute( fid, "grid_ocean", "node_coordinates", "lon_uv lat_uv" )
2782  call file_set_attribute( fid, "grid_ocean", "face_coordinates", "lon lat" )
2783  call file_set_attribute( fid, "grid_ocean", "edge1_coordinates", "lon_uy lat_uy" )
2784  call file_set_attribute( fid, "grid_ocean", "edge2_coordinates", "lon_xv lat_xv" )
2785  call file_set_attribute( fid, "grid_ocean", "vertical_dimensions", "oz: ozh (padding: none)" )
2786  end if
2787 
2788  if ( lkmax > 0 ) then
2789  call file_add_associatedvariable( fid, "grid_land" )
2790  call file_set_attribute( fid, "grid_land", "cf_role", "grid_topology" )
2791  call file_set_attribute( fid, "grid_land", "topology_dimension", (/ 2 /) )
2792  call file_set_attribute( fid, "grid_land", "node_dimensions", "xh yh" )
2793  call file_set_attribute( fid, "grid_land", "face_dimensions", "x: xh (padding: none) y: yh (padding: none)" )
2794  call file_set_attribute( fid, "grid_land", "node_coordinates", "lon_uv lat_uv" )
2795  call file_set_attribute( fid, "grid_land", "face_coordinates", "lon lat" )
2796  call file_set_attribute( fid, "grid_land", "edge1_coordinates", "lon_uy lat_uy" )
2797  call file_set_attribute( fid, "grid_land", "edge2_coordinates", "lon_xv lat_xv" )
2798  call file_set_attribute( fid, "grid_land", "vertical_dimensions", "lz: lzh (padding: none)" )
2799  end if
2800 
2801  if ( ukmax > 0 ) then
2802  call file_add_associatedvariable( fid, "grid_urban" )
2803  call file_set_attribute( fid, "grid_urban", "cf_role", "grid_topology" )
2804  call file_set_attribute( fid, "grid_urban", "topology_dimension", (/ 2 /) )
2805  call file_set_attribute( fid, "grid_urban", "node_dimensions", "xh yh" )
2806  call file_set_attribute( fid, "grid_urban", "face_dimensions", "x: xh (padding: none) y: yh (padding: none)" )
2807  call file_set_attribute( fid, "grid_urban", "node_coordinates", "lon_uv lat_uv" )
2808  call file_set_attribute( fid, "grid_urban", "face_coordinates", "lon lat" )
2809  call file_set_attribute( fid, "grid_urban", "edge1_coordinates", "lon_uy lat_uy" )
2810  call file_set_attribute( fid, "grid_urban", "edge2_coordinates", "lon_xv lat_xv" )
2811  call file_set_attribute( fid, "grid_urban", "vertical_dimensions", "uz: uzh (padding: none)" )
2812  end if
2813 
2814  call file_add_associatedvariable( fid, "grid_model" )
2815  call file_set_attribute( fid, "grid_model", "cf_role", "grid_topology" )
2816  call file_set_attribute( fid, "grid_model", "topology_dimension", (/ 2 /) )
2817  call file_set_attribute( fid, "grid_model", "node_dimensions", "FX FY" )
2818  call file_set_attribute( fid, "grid_model", "face_dimensions", "CX: FY (padding: none) CY: FY (padding: none)" )
2819  call file_set_attribute( fid, "grid_model", "vertical_dimensions", "CZ: FZ (padding: none)" )
2820 
2821  call file_add_associatedvariable( fid, "grid_model_global" )
2822  call file_set_attribute( fid, "grid_model_global", "cf_role", "grid_topology" )
2823  call file_set_attribute( fid, "grid_model_global", "topology_dimension", (/ 2 /) )
2824  call file_set_attribute( fid, "grid_model_global", "node_dimensions", "FXG FYG" )
2825  call file_set_attribute( fid, "grid_model_global", "face_dimensions", "CXG: FYG (padding: none) CYG: FYG (padding: none)" )
2826  call file_set_attribute( fid, "grid_model_global", "vertical_dimensions", "CZ: FZ (padding: none)" )
2827 
2828  call prof_rapend('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
2829 
2830  return
2831  end subroutine file_cartesc_def_axes
2832 
2833  !-----------------------------------------------------------------------------
2835  subroutine file_cartesc_write_axes( &
2836  fid, &
2837  haszcoord, &
2838  start )
2839  use scale_const, only: &
2840  undef => const_undef
2841  use scale_file, only: &
2842  file_opened, &
2843  file_single, &
2845  file_write_axis, &
2846  file_write_associatedcoordinate
2847  use scale_prc, only: &
2848  prc_myrank, &
2849  prc_ismaster
2850  use scale_prc_cartesc, only: &
2851  prc_2drank
2852  use scale_atmos_grid_cartesc, only: &
2883  use scale_ocean_grid_cartesc, only: &
2887  use scale_land_grid_cartesc, only: &
2891  use scale_urban_grid_cartesc, only: &
2895  implicit none
2896 
2897  integer, intent(in) :: fid
2898  logical, intent(in) :: haszcoord
2899  integer, intent(in) :: start(3)
2900 
2901  logical :: put_z, put_x, put_y
2902  integer :: XSB, XEB, YSB, YEB
2903 
2904  real(RP) :: z_bnds(2,KA), zh_bnds(2,0:KA)
2905  real(RP) :: oz_bnds(2,OKA), ozh_bnds(2,0:OKA)
2906  real(RP) :: lz_bnds(2,LKA), lzh_bnds(2,0:LKA)
2907  real(RP) :: uz_bnds(2,UKA), uzh_bnds(2,0:UKA)
2908  real(RP) :: x_bnds(2,IA), xh_bnds(2,0:IA)
2909  real(RP) :: y_bnds(2,JA), yh_bnds(2,0:JA)
2910 
2911  real(RP) :: FDXG(0:IAG), FDYG(0:JAG)
2912  real(RP) :: FDX(0:IA), FDY(0:JA)
2913 
2914  integer :: k, i, j
2915  !---------------------------------------------------------------------------
2916 
2917  if ( .not. file_opened(fid) ) return
2918 
2919  call prof_rapstart('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
2920 
2921  if ( file_get_aggregate(fid) ) then
2922  ! For parallel I/O, not all variables are written by all processes.
2923  ! 1. Let PRC_myrank 0 writes all z axes
2924  ! 2. Let processes (rankidx(2) == 0) write x axes (south-most processes)
2925  ! rankidx(1) == 0 writes west HALO
2926  ! rankidx(1) == PRC_NUM_X-1 writes east HALO
2927  ! others writes without HALO
2928  ! 3. Let processes (rankidx(1) == 0) write y axes (west-most processes)
2929  ! rankidx(1) == 0 writes south HALO
2930  ! rankidx(1) == PRC_NUM_Y-1 writes north HALO
2931  ! others writes without HALO
2932 
2933  put_z = ( prc_ismaster ) ! only master process output the vertical coordinates
2934  put_x = ( prc_2drank(prc_myrank,2) == 0 ) ! only south-most row processes write x coordinates
2935  put_y = ( prc_2drank(prc_myrank,1) == 0 ) ! only west-most column processes write y coordinates
2936  else
2937  put_z = .true.
2938  put_x = .true.
2939  put_y = .true.
2940  end if
2941 
2942  if ( haszcoord .and. put_z ) then
2943  ! atmos
2944  call file_write_axis( fid, 'z', atmos_grid_cartesc_cz(ks:ke), start(1:1) )
2945  do k = ks, ke
2946  z_bnds(1,k) = atmos_grid_cartesc_fz(k-1)
2947  z_bnds(2,k) = atmos_grid_cartesc_fz(k )
2948  end do
2949  call file_write_associatedcoordinate( fid, 'z_bnds', z_bnds(:,ks:ke), start(1:1) )
2950 
2951  call file_write_axis( fid, 'zh', atmos_grid_cartesc_fz(ks-1:ke) , start(1:1) )
2952  do k = ks-1, ke
2953  zh_bnds(1,k) = atmos_grid_cartesc_cz(k )
2954  zh_bnds(2,k) = atmos_grid_cartesc_cz(k+1)
2955  end do
2956  call file_write_associatedcoordinate( fid, 'zh_bnds', zh_bnds(:,ks-1:ke), start(1:1) )
2957 
2958  ! ocean
2959  if ( okmax > 0 ) then
2960  call file_write_axis( fid, 'oz', ocean_grid_cartesc_cz(oks:oke), start(1:1) )
2961  do k = oks, oke
2962  oz_bnds(1,k) = ocean_grid_cartesc_fz(k-1)
2963  oz_bnds(2,k) = ocean_grid_cartesc_fz(k )
2964  end do
2965  call file_write_associatedcoordinate( fid, 'oz_bnds', oz_bnds(:,oks:oke), start(1:1) )
2966 
2967  call file_write_axis( fid, 'ozh', ocean_grid_cartesc_fz(oks-1:oke), start(1:1) )
2968  ozh_bnds(1,oks-1) = ocean_grid_cartesc_fz(oks-1)
2969  do k = oks-1, oke-1
2970  ozh_bnds(2,k ) = ocean_grid_cartesc_cz(k+1)
2971  ozh_bnds(1,k+1) = ocean_grid_cartesc_cz(k+1)
2972  end do
2973  ozh_bnds(2,oke) = ocean_grid_cartesc_fz(oke)
2974  call file_write_associatedcoordinate( fid, 'ozh_bnds', ozh_bnds(:,oks-1:oke), start(1:1) )
2975  end if
2976 
2977  ! land
2978  if ( lkmax > 0 ) then
2979  call file_write_axis( fid, 'lz', land_grid_cartesc_cz(lks:lke), start(1:1) )
2980  do k = lks, lke
2981  lz_bnds(1,k) = land_grid_cartesc_fz(k-1)
2982  lz_bnds(2,k) = land_grid_cartesc_fz(k )
2983  end do
2984  call file_write_associatedcoordinate( fid, 'lz_bnds', lz_bnds(:,lks:lke), start(1:1) )
2985 
2986  call file_write_axis( fid, 'lzh', land_grid_cartesc_fz(lks-1:lke), start(1:1) )
2987  lzh_bnds(1,lks-1) = land_grid_cartesc_fz(lks-1)
2988  do k = lks-1, lke-1
2989  lzh_bnds(2,k ) = land_grid_cartesc_cz(k+1)
2990  lzh_bnds(1,k+1) = land_grid_cartesc_cz(k+1)
2991  end do
2992  lzh_bnds(2,lke) = land_grid_cartesc_fz(lke)
2993  call file_write_associatedcoordinate( fid, 'lzh_bnds', lzh_bnds(:,lks-1:lke), start(1:1) )
2994  end if
2995 
2996  ! urban
2997  if ( ukmax > 0 ) then
2998  call file_write_axis( fid, 'uz', urban_grid_cartesc_cz(uks:uke), start(1:1) )
2999  do k = uks, uke
3000  uz_bnds(1,k) = urban_grid_cartesc_fz(k-1)
3001  uz_bnds(2,k) = urban_grid_cartesc_fz(k )
3002  end do
3003  call file_write_associatedcoordinate( fid, 'uz_bnds', uz_bnds(:,uks:uke), start(1:1) )
3004 
3005  call file_write_axis( fid, 'uzh', urban_grid_cartesc_fz(uks-1:uke), start(1:1) )
3006  uzh_bnds(1,uks-1) = urban_grid_cartesc_fz(uks-1)
3007  do k = uks-1, uke-1
3008  uzh_bnds(2,k ) = urban_grid_cartesc_cz(k+1)
3009  uzh_bnds(1,k+1) = urban_grid_cartesc_cz(k+1)
3010  end do
3011  uzh_bnds(2,uke) = urban_grid_cartesc_fz(uke)
3012  call file_write_associatedcoordinate( fid, 'uzh_bnds', uzh_bnds(:,uks-1:uke), start(1:1) )
3013  end if
3014  end if
3015 
3016  if ( put_x ) then
3017  if ( file_get_aggregate(fid) ) then
3018  call file_write_axis( fid, 'x' , atmos_grid_cartesc_cx(isb2:ieb2), start(2:2) )
3019  do i = isb2, ieb2
3020  x_bnds(1,i) = atmos_grid_cartesc_fx(i-1)
3021  x_bnds(2,i) = atmos_grid_cartesc_fx(i )
3022  end do
3023  call file_write_associatedcoordinate( fid, 'x_bnds', x_bnds(:,isb2:ieb2), (/1,start(2)/) )
3024 
3025  call file_write_axis( fid, 'xh', atmos_grid_cartesc_fx(isb2:ieb2), start(2:2) )
3026  do i = isb2, ieb2-1
3027  xh_bnds(1,i) = atmos_grid_cartesc_cx(i )
3028  xh_bnds(2,i) = atmos_grid_cartesc_cx(i+1)
3029  end do
3030  xh_bnds(1,ieb2) = atmos_grid_cartesc_cx(ieb2)
3031  if ( ieb2 == ia ) then
3032  xh_bnds(2,ieb2) = atmos_grid_cartesc_fx(ieb2)
3033  else
3034  xh_bnds(2,ieb2) = atmos_grid_cartesc_cx(ieb2+1)
3035  end if
3036  call file_write_associatedcoordinate( fid, 'xh_bnds', xh_bnds(:,isb2:ieb2), (/1,start(2)/) )
3037  else
3038  call file_write_axis( fid, 'x' , atmos_grid_cartesc_cx(isb:ieb), start(2:2) )
3039  do i = isb2, ieb
3040  x_bnds(1,i) = atmos_grid_cartesc_fx(i-1)
3041  x_bnds(2,i) = atmos_grid_cartesc_fx(i )
3042  end do
3043  call file_write_associatedcoordinate( fid, 'x_bnds', x_bnds(:,isb:ieb), (/1,start(2)/) )
3044 
3045  call file_write_axis( fid, 'xh', atmos_grid_cartesc_fx(isb:ieb), start(2:2) )
3046  do i = isb, ieb-1
3047  xh_bnds(1,i) = atmos_grid_cartesc_cx(i )
3048  xh_bnds(2,i) = atmos_grid_cartesc_cx(i+1)
3049  end do
3050  xh_bnds(1,ieb) = atmos_grid_cartesc_cx(ieb)
3051  if ( ieb == ia ) then
3052  xh_bnds(2,ieb) = atmos_grid_cartesc_fx(ieb)
3053  else
3054  xh_bnds(2,ieb) = atmos_grid_cartesc_cx(ieb+1)
3055  end if
3056  call file_write_associatedcoordinate( fid, 'xh_bnds', xh_bnds(:,isb:ieb), (/1,start(2)/) )
3057  end if
3058  end if
3059 
3060  if ( put_y ) then
3061  if ( file_get_aggregate(fid) ) then
3062  call file_write_axis( fid, 'y' , atmos_grid_cartesc_cy(jsb2:jeb2), start(3:3) )
3063  do j = jsb2, jeb2
3064  y_bnds(1,j) = atmos_grid_cartesc_fy(j-1)
3065  y_bnds(2,j) = atmos_grid_cartesc_fy(j )
3066  end do
3067  call file_write_associatedcoordinate( fid, 'y_bnds', y_bnds(:,jsb2:jeb2), (/1,start(2)/) )
3068 
3069  call file_write_axis( fid, 'yh', atmos_grid_cartesc_fy(jsb2:jeb2), start(3:3) )
3070  do j = jsb2, jeb2-1
3071  yh_bnds(1,j) = atmos_grid_cartesc_cy(j )
3072  yh_bnds(2,j) = atmos_grid_cartesc_cy(j+1)
3073  end do
3074  yh_bnds(1,jeb2) = atmos_grid_cartesc_cy(jeb2)
3075  if ( jeb2 == ja ) then
3076  yh_bnds(2,jeb2) = atmos_grid_cartesc_fy(jeb2)
3077  else
3078  yh_bnds(2,jeb2) = atmos_grid_cartesc_cy(jeb2+1)
3079  end if
3080  call file_write_associatedcoordinate( fid, 'yh_bnds', yh_bnds(:,jsb2:jeb2), (/1,start(2)/) )
3081  else
3082  call file_write_axis( fid, 'y' , atmos_grid_cartesc_cy(jsb:jeb), start(3:3) )
3083  do j = jsb, jeb
3084  y_bnds(1,j) = atmos_grid_cartesc_fy(j-1)
3085  y_bnds(2,j) = atmos_grid_cartesc_fy(j )
3086  end do
3087  call file_write_associatedcoordinate( fid, 'y_bnds', y_bnds(:,jsb:jeb), (/1,start(2)/) )
3088 
3089  call file_write_axis( fid, 'yh', atmos_grid_cartesc_fy(jsb:jeb), start(3:3) )
3090  do j = jsb, jeb-1
3091  yh_bnds(1,j) = atmos_grid_cartesc_cy(j )
3092  yh_bnds(2,j) = atmos_grid_cartesc_cy(j+1)
3093  end do
3094  yh_bnds(1,jeb) = atmos_grid_cartesc_cy(jeb2)
3095  if ( jeb == ja ) then
3096  yh_bnds(2,jeb) = atmos_grid_cartesc_fy(jeb)
3097  else
3098  yh_bnds(2,jeb) = atmos_grid_cartesc_cy(jeb+1)
3099  end if
3100  call file_write_associatedcoordinate( fid, 'yh_bnds', yh_bnds(:,jsb:jeb), (/1,start(2)/) )
3101  end if
3102  end if
3103 
3104  fdxg(1:iag-1) = atmos_grid_cartesc_fdxg(:)
3105  fdxg(0 ) = undef
3106  fdxg(iag) = undef
3107  fdyg(1:jag-1) = atmos_grid_cartesc_fdyg(:)
3108  fdyg(0 ) = undef
3109  fdyg(jag) = undef
3110 
3111  fdx(1:ia-1) = atmos_grid_cartesc_fdx(:)
3112  fdx(0 ) = fdxg(is_ing-ihalo-1)
3113  fdx(ia) = fdxg(ie_ing+ihalo )
3114  fdy(1:ja-1) = atmos_grid_cartesc_fdy(:)
3115  fdy(0 ) = fdyg(js_ing-jhalo-1)
3116  fdy(ja) = fdyg(je_ing+jhalo )
3117 
3118  ! global coordinates (always including halo)
3119  if ( haszcoord .and. put_z ) then
3120  call file_write_axis( fid, 'CZ' , atmos_grid_cartesc_cz(:), start(1:1) )
3121  call file_write_axis( fid, 'FZ' , atmos_grid_cartesc_fz(:), start(1:1) )
3122  call file_write_axis( fid, 'CDZ' , atmos_grid_cartesc_cdz(:), start(1:1) )
3123  call file_write_axis( fid, 'FDZ' , atmos_grid_cartesc_fdz(:), start(1:1) )
3124  call file_write_axis( fid, 'CBFZ', atmos_grid_cartesc_cbfz(:), start(1:1) )
3125  call file_write_axis( fid, 'FBFZ', atmos_grid_cartesc_fbfz(:), start(1:1) )
3126 
3127  if ( okmax > 0 ) then
3128  call file_write_axis( fid, 'OCZ' , ocean_grid_cartesc_cz(:), start(1:1) )
3129  call file_write_axis( fid, 'OFZ' , ocean_grid_cartesc_fz(:), start(1:1) )
3130  call file_write_axis( fid, 'OCDZ', ocean_grid_cartesc_cdz(:), start(1:1) )
3131  end if
3132 
3133  if ( lkmax > 0 ) then
3134  call file_write_axis( fid, 'LCZ' , land_grid_cartesc_cz(:), start(1:1) )
3135  call file_write_axis( fid, 'LFZ' , land_grid_cartesc_fz(:), start(1:1) )
3136  call file_write_axis( fid, 'LCDZ', land_grid_cartesc_cdz(:), start(1:1) )
3137  end if
3138 
3139  if ( ukmax > 0 ) then
3140  call file_write_axis( fid, 'UCZ' , urban_grid_cartesc_cz(:), start(1:1) )
3141  call file_write_axis( fid, 'UFZ' , urban_grid_cartesc_fz(:), start(1:1) )
3142  call file_write_axis( fid, 'UCDZ', urban_grid_cartesc_cdz(:), start(1:1) )
3143  end if
3144  end if
3145 
3146  if ( file_get_aggregate(fid) ) then
3147  if ( prc_ismaster ) then
3148  call file_write_axis( fid, 'CX', atmos_grid_cartesc_cxg(:) )
3149  call file_write_axis( fid, 'CY', atmos_grid_cartesc_cyg(:) )
3150  call file_write_axis( fid, 'FX', atmos_grid_cartesc_fxg(:) )
3151  call file_write_axis( fid, 'FY', atmos_grid_cartesc_fyg(:) )
3152  call file_write_axis( fid, 'CDX', atmos_grid_cartesc_cdxg(:) )
3153  call file_write_axis( fid, 'CDY', atmos_grid_cartesc_cdyg(:) )
3154 
3155  call file_write_axis( fid, 'FDX', fdxg(:) )
3156  call file_write_axis( fid, 'FDY', fdyg(:) )
3157  call file_write_axis( fid, 'CBFX', atmos_grid_cartesc_cbfxg(:) )
3158  call file_write_axis( fid, 'CBFY', atmos_grid_cartesc_cbfyg(:) )
3159  call file_write_axis( fid, 'FBFX', atmos_grid_cartesc_fbfxg(:) )
3160  call file_write_axis( fid, 'FBFY', atmos_grid_cartesc_fbfyg(:) )
3161  endif
3162  else
3163  call file_write_axis( fid, 'CX', atmos_grid_cartesc_cx(:) )
3164  call file_write_axis( fid, 'CY', atmos_grid_cartesc_cy(:) )
3165  call file_write_axis( fid, 'FX', atmos_grid_cartesc_fx(:) )
3166  call file_write_axis( fid, 'FY', atmos_grid_cartesc_fy(:) )
3167  call file_write_axis( fid, 'CDX', atmos_grid_cartesc_cdx(:) )
3168  call file_write_axis( fid, 'CDY', atmos_grid_cartesc_cdy(:) )
3169  call file_write_axis( fid, 'FDX', fdx(:) )
3170  call file_write_axis( fid, 'FDY', fdy(:) )
3171  call file_write_axis( fid, 'CBFX', atmos_grid_cartesc_cbfx(:) )
3172  call file_write_axis( fid, 'CBFY', atmos_grid_cartesc_cbfy(:) )
3173  call file_write_axis( fid, 'FBFX', atmos_grid_cartesc_fbfx(:) )
3174  call file_write_axis( fid, 'FBFY', atmos_grid_cartesc_fbfy(:) )
3175  endif
3176 
3177  call file_write_axis( fid, 'CXG', atmos_grid_cartesc_cxg(:) )
3178  call file_write_axis( fid, 'CYG', atmos_grid_cartesc_cyg(:) )
3179  call file_write_axis( fid, 'FXG', atmos_grid_cartesc_fxg(:) )
3180  call file_write_axis( fid, 'FYG', atmos_grid_cartesc_fyg(:) )
3181  call file_write_axis( fid, 'CDXG', atmos_grid_cartesc_cdxg(:) )
3182  call file_write_axis( fid, 'CDYG', atmos_grid_cartesc_cdyg(:) )
3183  call file_write_axis( fid, 'FDXG', fdxg(:) )
3184  call file_write_axis( fid, 'FDYG', fdyg(:) )
3185  call file_write_axis( fid, 'CBFXG', atmos_grid_cartesc_cbfxg(:) )
3186  call file_write_axis( fid, 'CBFYG', atmos_grid_cartesc_cbfyg(:) )
3187  call file_write_axis( fid, 'FBFXG', atmos_grid_cartesc_fbfxg(:) )
3188  call file_write_axis( fid, 'FBFYG', atmos_grid_cartesc_fbfyg(:) )
3189 
3190  ! associate coordinates
3191  if ( file_get_aggregate(fid) ) then
3192  call file_write_associatedcoordinate( fid, 'lon' , axis_lon(:,:), start(2:3) )
3193  call file_write_associatedcoordinate( fid, 'lon_uy', axis_lonuy(:,:), start(2:3) )
3194  call file_write_associatedcoordinate( fid, 'lon_xv', axis_lonxv(:,:), start(2:3) )
3195  call file_write_associatedcoordinate( fid, 'lon_uv', axis_lonuv(:,:), start(2:3) )
3196  call file_write_associatedcoordinate( fid, 'lat' , axis_lat(:,:), start(2:3) )
3197  call file_write_associatedcoordinate( fid, 'lat_uy', axis_latuy(:,:), start(2:3) )
3198  call file_write_associatedcoordinate( fid, 'lat_xv', axis_latxv(:,:), start(2:3) )
3199  call file_write_associatedcoordinate( fid, 'lat_uv', axis_latuv(:,:), start(2:3) )
3200 
3201  if ( haszcoord ) then
3202  call file_write_associatedcoordinate( fid, 'topo', axis_topo(:,:), start(2:3) )
3203  end if
3204  call file_write_associatedcoordinate( fid, 'lsmask', axis_lsmask(:,:), start(2:3) )
3205 
3206  call file_write_associatedcoordinate( fid, 'cell_area', axis_area(:,:), start(2:3) )
3207  call file_write_associatedcoordinate( fid, 'cell_area_uy', axis_areauy(:,:), start(2:3) )
3208  call file_write_associatedcoordinate( fid, 'cell_area_xv', axis_areaxv(:,:), start(2:3) )
3209 
3210  if ( haszcoord ) then
3211  call file_write_associatedcoordinate( fid, 'height' , axis_hgt(:,:,:), start(1:3) )
3212  call file_write_associatedcoordinate( fid, 'height_wxy', axis_hgtwxy(:,:,:), start(1:3) )
3213 
3214  call file_write_associatedcoordinate( fid, 'cell_area_zuy_x', axis_areazuy_x(:,:,:), start(1:3) )
3215  call file_write_associatedcoordinate( fid, 'cell_area_zxv_y', axis_areazxv_y(:,:,:), start(1:3) )
3216  call file_write_associatedcoordinate( fid, 'cell_area_wuy_x', axis_areawuy_x(:,:,:), start(1:3) )
3217  call file_write_associatedcoordinate( fid, 'cell_area_wxv_y', axis_areawxv_y(:,:,:), start(1:3) )
3218  call file_write_associatedcoordinate( fid, 'cell_area_zxy_x', axis_areazxy_x(:,:,:), start(1:3) )
3219  call file_write_associatedcoordinate( fid, 'cell_area_zuv_y', axis_areazuv_y(:,:,:), start(1:3) )
3220  call file_write_associatedcoordinate( fid, 'cell_area_zuv_x', axis_areazuv_x(:,:,:), start(1:3) )
3221  call file_write_associatedcoordinate( fid, 'cell_area_zxy_y', axis_areazxy_y(:,:,:), start(1:3) )
3222 
3223  call file_write_associatedcoordinate( fid, 'cell_volume', axis_vol(:,:,:), start(1:3) )
3224  call file_write_associatedcoordinate( fid, 'cell_volume_wxy', axis_volwxy(:,:,:), start(1:3) )
3225  call file_write_associatedcoordinate( fid, 'cell_volume_zuy', axis_volzuy(:,:,:), start(1:3) )
3226  call file_write_associatedcoordinate( fid, 'cell_volume_zxv', axis_volzxv(:,:,:), start(1:3) )
3227 
3228  if ( okmax > 0 ) then
3229  call file_write_associatedcoordinate( fid, 'cell_volume_oxy', axis_volo(:,:,:), start(1:3) )
3230  end if
3231  if ( lkmax > 0 ) then
3232  call file_write_associatedcoordinate( fid, 'cell_volume_lxy', axis_voll(:,:,:), start(1:3) )
3233  end if
3234  if ( ukmax > 0 ) then
3235  call file_write_associatedcoordinate( fid, 'cell_volume_uxy', axis_volu(:,:,:), start(1:3) )
3236  end if
3237  end if
3238  else
3239  xsb = isb - isb2 + 1
3240  xeb = ieb - isb + xsb
3241  ysb = jsb - jsb2 + 1
3242  yeb = jeb - jsb + ysb
3243 
3244  call file_write_associatedcoordinate( fid, 'lon' , axis_lon(xsb:xeb,ysb:yeb), start(2:3) )
3245  call file_write_associatedcoordinate( fid, 'lon_uy', axis_lonuy(xsb:xeb,ysb:yeb), start(2:3) )
3246  call file_write_associatedcoordinate( fid, 'lon_xv', axis_lonxv(xsb:xeb,ysb:yeb), start(2:3) )
3247  call file_write_associatedcoordinate( fid, 'lon_uv', axis_lonuv(xsb:xeb,ysb:yeb), start(2:3) )
3248  call file_write_associatedcoordinate( fid, 'lat' , axis_lat(xsb:xeb,ysb:yeb), start(2:3) )
3249  call file_write_associatedcoordinate( fid, 'lat_uy', axis_latuy(xsb:xeb,ysb:yeb), start(2:3) )
3250  call file_write_associatedcoordinate( fid, 'lat_xv', axis_latxv(xsb:xeb,ysb:yeb), start(2:3) )
3251  call file_write_associatedcoordinate( fid, 'lat_uv', axis_latuv(xsb:xeb,ysb:yeb), start(2:3) )
3252 
3253  if ( haszcoord ) then
3254  call file_write_associatedcoordinate( fid, 'topo', axis_topo(xsb:xeb,ysb:yeb), start(2:3) )
3255  end if
3256  call file_write_associatedcoordinate( fid, 'lsmask', axis_lsmask(xsb:xeb,ysb:yeb), start(2:3) )
3257 
3258  call file_write_associatedcoordinate( fid, 'cell_area', axis_area(xsb:xeb,ysb:yeb), start(2:3) )
3259  call file_write_associatedcoordinate( fid, 'cell_area_uy', axis_areauy(xsb:xeb,ysb:yeb), start(2:3) )
3260  call file_write_associatedcoordinate( fid, 'cell_area_xv', axis_areaxv(xsb:xeb,ysb:yeb), start(2:3) )
3261 
3262  if ( haszcoord ) then
3263  call file_write_associatedcoordinate( fid, 'height' , axis_hgt(:,xsb:xeb,ysb:yeb), start(1:3) )
3264  call file_write_associatedcoordinate( fid, 'height_wxy', axis_hgtwxy(:,xsb:xeb,ysb:yeb), start(1:3) )
3265 
3266  call file_write_associatedcoordinate( fid, 'cell_area_zuy_x', axis_areazuy_x(:,xsb:xeb,ysb:yeb), start(2:3) )
3267  call file_write_associatedcoordinate( fid, 'cell_area_zxv_y', axis_areazxv_y(:,xsb:xeb,ysb:yeb), start(2:3) )
3268  call file_write_associatedcoordinate( fid, 'cell_area_wuy_x', axis_areawuy_x(:,xsb:xeb,ysb:yeb), start(2:3) )
3269  call file_write_associatedcoordinate( fid, 'cell_area_wxv_y', axis_areawxv_y(:,xsb:xeb,ysb:yeb), start(2:3) )
3270  call file_write_associatedcoordinate( fid, 'cell_area_zxy_x', axis_areazxy_x(:,xsb:xeb,ysb:yeb), start(2:3) )
3271  call file_write_associatedcoordinate( fid, 'cell_area_zuv_y', axis_areazuv_y(:,xsb:xeb,ysb:yeb), start(2:3) )
3272  call file_write_associatedcoordinate( fid, 'cell_area_zuv_x', axis_areazuv_x(:,xsb:xeb,ysb:yeb), start(2:3) )
3273  call file_write_associatedcoordinate( fid, 'cell_area_zxy_y', axis_areazxy_y(:,xsb:xeb,ysb:yeb), start(2:3) )
3274 
3275  call file_write_associatedcoordinate( fid, 'cell_volume', axis_vol(:,xsb:xeb,ysb:yeb), start(1:3) )
3276  call file_write_associatedcoordinate( fid, 'cell_volume_wxy', axis_volwxy(:,xsb:xeb,ysb:yeb), start(1:3) )
3277  call file_write_associatedcoordinate( fid, 'cell_volume_zuy', axis_volzuy(:,xsb:xeb,ysb:yeb), start(1:3) )
3278  call file_write_associatedcoordinate( fid, 'cell_volume_zxv', axis_volzxv(:,xsb:xeb,ysb:yeb), start(1:3) )
3279 
3280  if ( okmax > 0 ) then
3281  call file_write_associatedcoordinate( fid, 'cell_volume_oxy', axis_volo(:,xsb:xeb,ysb:yeb), start(1:3) )
3282  end if
3283  if ( lkmax > 0 ) then
3284  call file_write_associatedcoordinate( fid, 'cell_volume_lxy', axis_voll(:,xsb:xeb,ysb:yeb), start(1:3) )
3285  end if
3286  if ( ukmax > 0 ) then
3287  call file_write_associatedcoordinate( fid, 'cell_volume_uxy', axis_volu(:,xsb:xeb,ysb:yeb), start(1:3) )
3288  end if
3289  end if
3290  end if
3291 
3292  call prof_rapend('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
3293 
3294  return
3295  end subroutine file_cartesc_write_axes
3296 
3297  !-----------------------------------------------------------------------------
3299  subroutine file_cartesc_def_var( &
3300  fid, &
3301  varname, desc, unit, &
3302  dim_type, datatype, &
3303  vid, &
3304  standard_name, &
3305  timeintv, nsteps, &
3306  cell_measures )
3307  use scale_file_h, only: &
3308  file_real8, &
3309  file_real4
3310  use scale_file, only: &
3311  file_opened, &
3312  file_single, &
3314  file_set_attribute
3315  use scale_prc, only: &
3316  prc_abort
3317  use scale_prc_cartesc, only: &
3318  prc_twod
3319  use scale_mapprojection, only: &
3321  implicit none
3322 
3323  integer, intent(in) :: fid
3324  character(len=*), intent(in) :: varname
3325  character(len=*), intent(in) :: desc
3326  character(len=*), intent(in) :: unit
3327  character(len=*), intent(in) :: dim_type
3328  character(len=*), intent(in) :: datatype
3329 
3330  integer, intent(out) :: vid
3331 
3332  character(len=*), intent(in), optional :: standard_name
3333  real(dp), intent(in), optional :: timeintv
3334  integer, intent(in), optional :: nsteps
3335  character(len=*), intent(in), optional :: cell_measures
3336 
3337  character(len=H_MID) :: standard_name_
3338  character(len=H_SHORT) :: cell_measures_
3339 
3340  character(len=H_SHORT) :: dimtype
3341 
3342  integer :: dtype, elm_size, ndims
3343  integer :: dimid, n
3344  !---------------------------------------------------------------------------
3345 
3346  if ( .not. file_opened(fid) ) return
3347 
3348  call prof_rapstart('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
3349 
3350  if ( datatype == 'REAL8' ) then
3351  dtype = file_real8
3352  elm_size = 4
3353  elseif( datatype == 'REAL4' ) then
3354  dtype = file_real4
3355  elm_size = 8
3356  else
3357  if ( rp == 8 ) then
3358  dtype = file_real8
3359  elm_size = 8
3360  elseif( rp == 4 ) then
3361  dtype = file_real4
3362  elm_size = 4
3363  else
3364  log_error("FILE_CARTESC_def_var",*) 'unsupported data type. Check!', trim(datatype), ' item:',trim(varname)
3365  call prc_abort
3366  endif
3367  endif
3368 
3369  if ( prc_twod ) then
3370  select case( dim_type )
3371  case ( "UY" )
3372  dimtype = "XY"
3373  case ( "UV" )
3374  dimtype = "XV"
3375  case ( "ZXHY" )
3376  dimtype = "ZXY"
3377  case ( "ZXHYH")
3378  dimtype = "ZXYH"
3379  case ( "ZHXHY" )
3380  dimtype = "ZHXY"
3381  case default
3382  dimtype = dim_type
3383  end select
3384  else
3385  dimtype = dim_type
3386  end if
3387 
3388  dimid = -1
3389  do n = 1, file_cartesc_ndims
3390  if ( file_cartesc_dims(n)%name == dimtype ) then
3391  dimid = n
3392  exit
3393  end if
3394  end do
3395  if ( dimid <= -1 ) then
3396  log_error("FILE_CARTESC_def_var",*) 'dim_type is not supported: ', trim(dimtype)
3397  call prc_abort
3398  end if
3399 
3400  if ( present(nsteps) ) then
3401  write_buf_amount(fid) = write_buf_amount(fid) + file_cartesc_dims(dimid)%size * elm_size * nsteps
3402  else
3403  write_buf_amount(fid) = write_buf_amount(fid) + file_cartesc_dims(dimid)%size * elm_size
3404  end if
3405 
3406  ndims = file_cartesc_dims(dimid)%ndims
3407 
3408  if ( present(standard_name) ) then
3409  standard_name_ = standard_name
3410  else
3411  standard_name_ = ""
3412  end if
3413 
3414  if ( present(timeintv) ) then ! 3D/4D variable with time dimension
3415  call file_def_variable( fid, varname, desc, unit, standard_name_, & ! [IN]
3416  ndims, file_cartesc_dims(dimid)%dims(1:ndims), dtype, & ! [IN]
3417  vid, & ! [OUT]
3418  time_int=timeintv ) ! [IN]
3419  else
3420  call file_def_variable( fid, varname, desc, unit, standard_name_, & ! [IN]
3421  ndims, file_cartesc_dims(dimid)%dims(1:ndims), dtype, & ! [IN]
3422  vid ) ! [OUT]
3423  endif
3424 
3425  if ( present(cell_measures) ) then
3426  cell_measures_ = cell_measures
3427  select case ( cell_measures )
3428  case ( "area" )
3429  if ( file_cartesc_dims(dimid)%area == "" ) then
3430  log_error("FILE_CARTESC_def_var",*) 'area is not supported for ', trim(dimtype), ' as cell_measures'
3431  call prc_abort
3432  end if
3433  case ( "area_z" )
3434  if ( file_cartesc_dims(dimid)%area == "" ) then
3435  log_error("FILE_CARTESC_def_var",*) 'area_z is not supported for ', trim(dimtype), ' as cell_measures'
3436  call prc_abort
3437  end if
3438  case ( "area_x" )
3439  if ( file_cartesc_dims(dimid)%area_x == "" ) then
3440  log_error("FILE_CARTESC_def_var",*) 'area_x is not supported for ', trim(dimtype), ' as cell_measures'
3441  call prc_abort
3442  end if
3443  case ( "area_y" )
3444  if ( file_cartesc_dims(dimid)%area_y == "" ) then
3445  log_error("FILE_CARTESC_def_var",*) 'area_y is not supported for ', trim(dimtype), ' as cell_measures'
3446  call prc_abort
3447  end if
3448  case ( "volume" )
3449  if ( file_cartesc_dims(dimid)%volume == "" ) then
3450  log_error("FILE_CARTESC_def_var",*) 'volume is not supported for ', trim(dimtype), ' as cell_measures'
3451  call prc_abort
3452  end if
3453  case default
3454  log_error("FILE_CARTESC_def_var",*) 'cell_measures must be "area" or "volume"'
3455  call prc_abort
3456  end select
3457  else if ( ndims == 2 ) then
3458  cell_measures_ = "area"
3459  else if ( ndims == 3 ) then
3460  cell_measures_ = "volume"
3461  else
3462  cell_measures_ = ""
3463  end if
3464 
3465  select case( cell_measures_ )
3466  case ( "area", "area_z" )
3467  call file_set_attribute( fid, varname, "cell_measures", "area: "//trim(file_cartesc_dims(dimid)%area) )
3468  case ( "area_x" )
3469  call file_set_attribute( fid, varname, "cell_measures", "area: "//trim(file_cartesc_dims(dimid)%area_x) )
3470  case ( "area_y" )
3471  call file_set_attribute( fid, varname, "cell_measures", "area: "//trim(file_cartesc_dims(dimid)%area_y) )
3472  case ( "volume" )
3473  call file_set_attribute( fid, varname, "cell_measures", "volume: "//trim(file_cartesc_dims(dimid)%volume) )
3474  end select
3475 
3476  ! mapping
3477  if ( file_cartesc_dims(dimid)%mapping .and. mapprojection_mappinginfo%mapping_name /= "" ) then
3478  call file_set_attribute( fid, varname, "grid_mapping", mapprojection_mappinginfo%mapping_name )
3479  end if
3480 
3481  ! SGRID
3482  if ( file_cartesc_dims(dimid)%location /= "" ) then
3483  call file_set_attribute( fid, varname, "grid", file_cartesc_dims(dimid)%grid )
3484  call file_set_attribute( fid, varname, "location", file_cartesc_dims(dimid)%location )
3485  end if
3486 
3487  call prof_rapend('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
3488 
3489  return
3490  end subroutine file_cartesc_def_var
3491 
3492  !-----------------------------------------------------------------------------
3494  subroutine file_cartesc_write_var_1d( &
3495  fid, &
3496  vid, &
3497  var, &
3498  varname, &
3499  dim_type )
3500  use scale_file, only: &
3502  file_opened, &
3503  file_single, &
3504  file_write
3505  use scale_prc, only: &
3506  prc_myrank, &
3507  prc_abort
3508  use scale_prc_cartesc, only: &
3509  prc_2drank
3510  use scale_time, only: &
3511  nowdaysec => time_nowdaysec
3512  implicit none
3513 
3514  integer, intent(in) :: fid
3515  integer, intent(in) :: vid
3516  real(RP), intent(in) :: var(:)
3517  character(len=*), intent(in) :: varname
3518  character(len=*), intent(in) :: dim_type
3519 
3520  integer :: dim1_S, dim1_E
3521  integer :: rankidx(2)
3522  integer :: start(1) ! used only when AGGREGATE is .true.
3523  logical :: exec
3524  !---------------------------------------------------------------------------
3525 
3526  if ( .not. file_opened(fid) ) return
3527 
3528  call prof_rapstart('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
3529 
3530  rankidx(1) = prc_2drank(prc_myrank,1)
3531  rankidx(2) = prc_2drank(prc_myrank,2)
3532 
3533  if ( dim_type == 'Z' ) then
3534  dim1_s = ks
3535  dim1_e = ke
3536  start(1) = 1
3537  if( file_get_aggregate(fid) .AND. prc_myrank > 0 ) then
3538  exec = .false. ! only rank 0 writes
3539  else
3540  exec = .true.
3541  end if
3542  elseif( dim_type == 'X' ) then
3543  if ( file_get_aggregate(fid) ) then
3544  exec = ( rankidx(2) == 0 ) ! only south most row processes write
3545  dim1_s = isb2
3546  dim1_e = ieb2
3547  else
3548  exec = .true.
3549  dim1_s = isb
3550  dim1_e = ieb
3551  end if
3552  start(1) = isga
3553  elseif( dim_type == 'Y' ) then
3554  if ( file_get_aggregate(fid) ) then
3555  exec = ( rankidx(1) == 0 ) ! only west most column processes write
3556  dim1_s = jsb2
3557  dim1_e = jeb2
3558  else
3559  exec = .true.
3560  dim1_s = jsb
3561  dim1_e = jeb
3562  end if
3563  start(1) = jsga
3564  else
3565  log_error("FILE_CARTESC_write_var_1D",*) 'unsupported dimenstion type. Check! dim_type:', trim(dim_type), ', item:',trim(varname)
3566  call prc_abort
3567  endif
3568 
3569  if( exec ) call file_write( vid, var(dim1_s:dim1_e), & ! [IN]
3570  nowdaysec, nowdaysec, start=start ) ! [IN]
3571 
3572  call prof_rapend('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
3573 
3574  return
3575  end subroutine file_cartesc_write_var_1d
3576 
3577  !-----------------------------------------------------------------------------
3579  subroutine file_cartesc_write_var_2d( &
3580  fid, &
3581  vid, &
3582  var, &
3583  varname, &
3584  dim_type, &
3585  fill_halo )
3586  use scale_file_h, only: &
3587  rmiss => file_rmiss
3588  use scale_file, only: &
3590  file_opened, &
3591  file_single, &
3592  file_write
3593  use scale_prc, only: &
3594  prc_myrank, &
3595  prc_abort
3596  use scale_prc_cartesc, only: &
3597  prc_2drank, &
3598  prc_num_x, &
3599  prc_num_y
3600  use scale_time, only: &
3601  nowdaysec => time_nowdaysec
3602  implicit none
3603 
3604  integer, intent(in) :: fid
3605  integer, intent(in) :: vid
3606  real(RP), intent(in) :: var(:,:)
3607  character(len=*), intent(in) :: varname
3608  character(len=*), intent(in) :: dim_type
3609  logical, intent(in), optional :: fill_halo
3610 
3611  real(RP) :: varhalo( size(var(:,1)), size(var(1,:)) )
3612 
3613  integer :: dim1_S, dim1_E
3614  integer :: dim2_S, dim2_E
3615 
3616  integer :: i, j
3617  logical :: fill_halo_
3618  integer :: rankidx(2)
3619  integer :: start(2) ! used only when AGGREGATE is .true.
3620  logical :: exec
3621  !---------------------------------------------------------------------------
3622 
3623  if ( .not. file_opened(fid) ) return
3624 
3625  call prof_rapstart('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
3626 
3627  rankidx(1) = prc_2drank(prc_myrank,1)
3628  rankidx(2) = prc_2drank(prc_myrank,2)
3629 
3630  start(1) = isga
3631  start(2) = jsga
3632 
3633  fill_halo_ = .false.
3634  if( present(fill_halo) ) fill_halo_ = fill_halo
3635 
3636  if ( dim_type == 'XY' &
3637  .OR. dim_type == 'UY' &
3638  .OR. dim_type == 'XV' &
3639  .OR. dim_type == 'UV' ) then
3640  if ( file_get_aggregate(fid) ) then
3641  dim1_s = isb2
3642  dim1_e = ieb2
3643  dim2_s = jsb2
3644  dim2_e = jeb2
3645  else
3646  dim1_s = isb
3647  dim1_e = ieb
3648  dim2_s = jsb
3649  dim2_e = jeb
3650  endif
3651  exec = .true.
3652  elseif( dim_type == 'ZX' ) then
3653  dim1_s = ks
3654  dim1_e = ke
3655  start(2) = start(1)
3656  start(1) = 1
3657  if ( file_get_aggregate(fid) ) then
3658  exec = ( rankidx(2) == 0 ) ! only south most row processes write
3659  dim2_s = isb2
3660  dim2_e = ieb2
3661  else
3662  exec = .true.
3663  dim2_s = isb
3664  dim2_e = ieb
3665  endif
3666  else
3667  log_error("FILE_CARTESC_write_var_2D",*) 'unsupported dimension type. Check! dim_type:', trim(dim_type), ', item:',trim(varname)
3668  call prc_abort
3669  endif
3670 
3671  if ( exec ) then
3672  if ( fill_halo_ ) then ! fill halo cells with RMISS
3673  do j = js, je
3674  do i = is, ie
3675  varhalo(i,j) = var(i,j)
3676  end do
3677  end do
3678 
3679  ! W halo
3680  do j = 1, ja
3681  do i = 1, is-1
3682  varhalo(i,j) = rmiss
3683  enddo
3684  enddo
3685  ! E halo
3686  do j = 1, ja
3687  do i = ie+1, ia
3688  varhalo(i,j) = rmiss
3689  enddo
3690  enddo
3691  ! S halo
3692  do j = 1, js-1
3693  do i = 1, ia
3694  varhalo(i,j) = rmiss
3695  enddo
3696  enddo
3697  ! N halo
3698  do j = je+1, ja
3699  do i = 1, ia
3700  varhalo(i,j) = rmiss
3701  enddo
3702  enddo
3703 
3704  call file_write( vid, varhalo(dim1_s:dim1_e,dim2_s:dim2_e), &
3705  nowdaysec, nowdaysec, start ) ! [IN]
3706  else
3707  call file_write( vid, var(dim1_s:dim1_e,dim2_s:dim2_e), &
3708  nowdaysec, nowdaysec, start ) ! [IN]
3709  endif
3710 
3711  endif
3712 
3713  call prof_rapend('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
3714 
3715  return
3716  end subroutine file_cartesc_write_var_2d
3717 
3718  !-----------------------------------------------------------------------------
3720  subroutine file_cartesc_write_var_3d( &
3721  fid, &
3722  vid, &
3723  var, &
3724  varname, &
3725  dim_type, &
3726  fill_halo )
3727  use scale_file_h, only: &
3728  rmiss => file_rmiss
3729  use scale_file, only: &
3731  file_opened, &
3732  file_single, &
3733  file_write
3734  use scale_prc, only: &
3735  prc_myrank, &
3736  prc_abort
3737  use scale_prc_cartesc, only: &
3738  prc_2drank, &
3739  prc_num_x, &
3740  prc_num_y
3741  use scale_time, only: &
3742  nowdaysec => time_nowdaysec
3743  implicit none
3744 
3745  integer, intent(in) :: fid
3746  integer, intent(in) :: vid
3747  real(RP), intent(in) :: var(:,:,:)
3748  character(len=*), intent(in) :: varname
3749  character(len=*), intent(in) :: dim_type
3750 
3751  logical, intent(in), optional :: fill_halo
3752 
3753  real(RP) :: varhalo( size(var(:,1,1)), size(var(1,:,1)), size(var(1,1,:)) )
3754 
3755  integer :: dim1_S, dim1_E, dim1_max
3756  integer :: dim2_S, dim2_E
3757  integer :: dim3_S, dim3_E
3758 
3759  integer :: i, j, k
3760  logical :: fill_halo_
3761  integer :: rankidx(2)
3762  integer :: start(3) ! used only when AGGREGATE is .true.
3763  !---------------------------------------------------------------------------
3764 
3765  if ( .not. file_opened(fid) ) return
3766 
3767  call prof_rapstart('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
3768 
3769  fill_halo_ = .false.
3770  if( present(fill_halo) ) fill_halo_ = fill_halo
3771 
3772  rankidx(1) = prc_2drank(prc_myrank,1)
3773  rankidx(2) = prc_2drank(prc_myrank,2)
3774 
3775  start(1) = 1
3776  start(2) = isga
3777  start(3) = jsga
3778 
3779  if ( dim_type == 'ZXY' &
3780  .OR. dim_type == 'ZXHY' &
3781  .OR. dim_type == 'ZXYH' &
3782  .OR. dim_type == 'ZXHYH' ) then
3783  dim1_max = kmax
3784  dim1_s = ks
3785  dim1_e = ke
3786  elseif ( dim_type == 'ZHXY' &
3787  .OR. dim_type == 'ZHXHY' &
3788  .OR. dim_type == 'ZHXYH' ) then
3789  dim1_max = kmax+1
3790  dim1_s = ks-1
3791  dim1_e = ke
3792  elseif( dim_type == 'OXY' ) then
3793  dim1_max = okmax
3794  dim1_s = oks
3795  dim1_e = oke
3796  elseif( dim_type == 'LXY' ) then
3797  dim1_max = lkmax
3798  dim1_s = lks
3799  dim1_e = lke
3800  elseif( dim_type == 'UXY' ) then
3801  dim1_max = ukmax
3802  dim1_s = uks
3803  dim1_e = uke
3804  else
3805  log_error("FILE_CARTESC_write_var_3D",*) 'unsupported dimension type. Check! dim_type:', trim(dim_type), ', item:',trim(varname)
3806  call prc_abort
3807  endif
3808 
3809  if ( file_get_aggregate(fid) ) then
3810  dim2_s = isb2
3811  dim2_e = ieb2
3812  dim3_s = jsb2
3813  dim3_e = jeb2
3814  else
3815  dim2_s = isb
3816  dim2_e = ieb
3817  dim3_s = jsb
3818  dim3_e = jeb
3819  endif
3820 
3821  if ( fill_halo_ ) then
3822  !$omp parallel do
3823  do j = js, je
3824  do i = is, ie
3825  do k = 1, dim1_max
3826  varhalo(k,i,j) = var(k,i,j)
3827  enddo
3828  enddo
3829  enddo
3830 
3831  ! W halo
3832  do j = 1, ja
3833  do i = 1, is-1
3834  do k = 1, dim1_max
3835  varhalo(k,i,j) = rmiss
3836  enddo
3837  enddo
3838  enddo
3839  ! E halo
3840  do j = 1, ja
3841  do i = ie+1, ia
3842  do k = 1, dim1_max
3843  varhalo(k,i,j) = rmiss
3844  enddo
3845  enddo
3846  enddo
3847  ! S halo
3848  do j = 1, js-1
3849  do i = 1, ia
3850  do k = 1, dim1_max
3851  varhalo(k,i,j) = rmiss
3852  enddo
3853  enddo
3854  enddo
3855  ! N halo
3856  do j = je+1, ja
3857  do i = 1, ia
3858  do k = 1, dim1_max
3859  varhalo(k,i,j) = rmiss
3860  enddo
3861  enddo
3862  enddo
3863 
3864  call file_write( vid, varhalo(dim1_s:dim1_e,dim2_s:dim2_e,dim3_s:dim3_e), &
3865  nowdaysec, nowdaysec, start ) ! [IN]
3866  else
3867  call file_write( vid, var(dim1_s:dim1_e,dim2_s:dim2_e,dim3_s:dim3_e), &
3868  nowdaysec, nowdaysec, start ) ! [IN]
3869  endif
3870 
3871  call prof_rapend('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
3872 
3873  return
3874  end subroutine file_cartesc_write_var_3d
3875 
3876  !-----------------------------------------------------------------------------
3878  subroutine file_cartesc_write_var_3d_t( &
3879  fid, &
3880  vid, &
3881  var, &
3882  varname, &
3883  dim_type, &
3884  timeintv, &
3885  timetarg, &
3886  timeofs, &
3887  fill_halo )
3888  use scale_file_h, only: &
3889  rmiss => file_rmiss
3890  use scale_file, only: &
3892  file_opened, &
3893  file_single, &
3894  file_write
3895  use scale_prc, only: &
3896  prc_myrank, &
3897  prc_abort
3898  use scale_prc_cartesc, only: &
3899  prc_2drank, &
3900  prc_num_x, &
3901  prc_num_y
3902  implicit none
3903 
3904  integer, intent(in) :: fid
3905  integer, intent(in) :: vid
3906  real(RP), intent(in) :: var(:,:,:)
3907  character(len=*), intent(in) :: varname
3908  character(len=*), intent(in) :: dim_type
3909  real(DP), intent(in) :: timeintv
3910 
3911  integer, intent(in), optional :: timetarg
3912  real(DP), intent(in), optional :: timeofs
3913  logical, intent(in), optional :: fill_halo
3914 
3915  real(RP) :: varhalo( size(var(:,1,1)), size(var(1,:,1)) )
3916 
3917  integer :: dim1_S, dim1_E
3918  integer :: dim2_S, dim2_E
3919 
3920  real(DP) :: time_interval, nowtime
3921 
3922  integer :: step
3923  integer :: i, j, n
3924  logical :: fill_halo_
3925  real(DP) :: timeofs_
3926  integer :: rankidx(2)
3927  integer :: start(2) ! used only when AGGREGATE is .true.
3928  !---------------------------------------------------------------------------
3929 
3930  if ( .not. file_opened(fid) ) return
3931 
3932  call prof_rapstart('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
3933 
3934  fill_halo_ = .false.
3935  if( present(fill_halo) ) fill_halo_ = fill_halo
3936 
3937  timeofs_ = 0.0_dp
3938  if( present(timeofs) ) timeofs_ = timeofs
3939 
3940  time_interval = timeintv
3941  step = size(var(isb,jsb,:))
3942 
3943  rankidx(1) = prc_2drank(prc_myrank,1)
3944  rankidx(2) = prc_2drank(prc_myrank,2)
3945 
3946  if ( dim_type == 'XYT' ) then
3947  if ( file_get_aggregate(fid) ) then
3948  dim1_s = isb2
3949  dim1_e = ieb2
3950  dim2_s = jsb2
3951  dim2_e = jeb2
3952  else
3953  dim1_s = isb
3954  dim1_e = ieb
3955  dim2_s = jsb
3956  dim2_e = jeb
3957  end if
3958  else
3959  log_error("FILE_CARTESC_write_var_3D_t",*) 'unsupported dimension type. Check! dim_type:', trim(dim_type), ', item:',trim(varname)
3960  call prc_abort
3961  endif
3962 
3963  start(1) = isga
3964  start(2) = jsga
3965  ! start(3) time dimension will be set in file_write_data()
3966 
3967  if ( present(timetarg) ) then
3968  nowtime = timeofs_ + (timetarg-1) * time_interval
3969 
3970  if ( fill_halo_ ) then
3971  do j = js, je
3972  do i = is, ie
3973  varhalo(i,j) = var(i,j,timetarg)
3974  end do
3975  end do
3976 
3977  ! W halo
3978  do j = 1, ja
3979  do i = 1, is-1
3980  varhalo(i,j) = rmiss
3981  enddo
3982  enddo
3983  ! E halo
3984  do j = 1, ja
3985  do i = ie+1, ia
3986  varhalo(i,j) = rmiss
3987  enddo
3988  enddo
3989  ! S halo
3990  do j = 1, js-1
3991  do i = 1, ia
3992  varhalo(i,j) = rmiss
3993  enddo
3994  enddo
3995  ! N halo
3996  do j = je+1, ja
3997  do i = 1, ia
3998  varhalo(i,j) = rmiss
3999  enddo
4000  enddo
4001 
4002  call file_write( vid, varhalo(dim1_s:dim1_e,dim2_s:dim2_e), &
4003  nowtime, nowtime, start ) ! [IN]
4004  else
4005  call file_write( vid, var(dim1_s:dim1_e,dim2_s:dim2_e,timetarg), &
4006  nowtime, nowtime, start ) ! [IN]
4007  endif
4008  else
4009  nowtime = timeofs_
4010  do n = 1, step
4011  if ( fill_halo_ ) then
4012  do j = js, je
4013  do i = is, ie
4014  varhalo(i,j) = var(i,j,n)
4015  end do
4016  end do
4017 
4018  ! W halo
4019  do j = 1, ja
4020  do i = 1, is-1
4021  varhalo(i,j) = rmiss
4022  enddo
4023  enddo
4024  ! E halo
4025  do j = 1, ja
4026  do i = ie+1, ia
4027  varhalo(i,j) = rmiss
4028  enddo
4029  enddo
4030  ! S halo
4031  do j = 1, js-1
4032  do i = 1, ia
4033  varhalo(i,j) = rmiss
4034  enddo
4035  enddo
4036  ! N halo
4037  do j = je+1, ja
4038  do i = 1, ia
4039  varhalo(i,j) = rmiss
4040  enddo
4041  enddo
4042 
4043  call file_write( vid, varhalo(dim1_s:dim1_e,dim2_s:dim2_e), &
4044  nowtime, nowtime, start ) ! [IN]
4045  else
4046  call file_write( vid, var(dim1_s:dim1_e,dim2_s:dim2_e,n), &
4047  nowtime, nowtime, start ) ! [IN]
4048  endif
4049  nowtime = nowtime + time_interval
4050  enddo
4051  endif
4052 
4053  call prof_rapend('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
4054 
4055  return
4056  end subroutine file_cartesc_write_var_3d_t
4057 
4058  !-----------------------------------------------------------------------------
4060  subroutine file_cartesc_write_var_4d( &
4061  fid, &
4062  vid, &
4063  var, &
4064  varname, &
4065  dim_type, &
4066  timeintv, &
4067  timetarg, &
4068  timeofs, &
4069  fill_halo )
4070  use scale_file_h, only: &
4071  rmiss => file_rmiss
4072  use scale_file, only: &
4074  file_opened, &
4075  file_single, &
4076  file_write, &
4077  file_flush
4078  use scale_prc, only: &
4079  prc_myrank, &
4080  prc_abort
4081  use scale_prc_cartesc, only: &
4082  prc_2drank, &
4083  prc_num_x, &
4084  prc_num_y
4085  implicit none
4086 
4087  integer, intent(in) :: fid
4088  integer, intent(in) :: vid
4089  real(RP), intent(in) :: var(:,:,:,:)
4090  character(len=*), intent(in) :: varname
4091  character(len=*), intent(in) :: dim_type
4092  real(DP), intent(in) :: timeintv
4093 
4094  integer, intent(in), optional :: timetarg
4095  real(DP), intent(in), optional :: timeofs
4096  logical, intent(in), optional :: fill_halo
4097 
4098  real(RP) :: varhalo( size(var(:,1,1,1)), size(var(1,:,1,1)), size(var(1,1,:,1)) )
4099 
4100  integer :: dim1_S, dim1_E, dim1_max
4101  integer :: dim2_S, dim2_E
4102  integer :: dim3_S, dim3_E
4103 
4104  real(DP) :: time_interval, nowtime
4105 
4106  integer :: step
4107  integer :: i, j, k, n
4108  logical :: fill_halo_
4109  real(DP) :: timeofs_
4110  integer :: rankidx(2)
4111  integer :: start(3) ! used only when AGGREGATE is .true.
4112  !---------------------------------------------------------------------------
4113 
4114  if ( .not. file_opened(fid) ) return
4115 
4116  call prof_rapstart('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
4117 
4118  fill_halo_ = .false.
4119  if( present(fill_halo) ) fill_halo_ = fill_halo
4120 
4121  timeofs_ = 0.0_dp
4122  if( present(timeofs) ) timeofs_ = timeofs
4123 
4124  rankidx(1) = prc_2drank(prc_myrank,1)
4125  rankidx(2) = prc_2drank(prc_myrank,2)
4126 
4127  start(1) = 1
4128  start(2) = isga
4129  start(3) = jsga
4130  ! start(4) time dimension will be set in file_write_data()
4131 
4132  time_interval = timeintv
4133  step = size(var,4)
4134 
4135  if ( file_get_aggregate(fid) ) then
4136  dim2_s = isb2
4137  dim2_e = ieb2
4138  dim3_s = jsb2
4139  dim3_e = jeb2
4140  else
4141  dim2_s = isb
4142  dim2_e = ieb
4143  dim3_s = jsb
4144  dim3_e = jeb
4145  endif
4146 
4147  if ( dim_type == 'ZXYT' &
4148  .OR. dim_type == 'ZXHYT' &
4149  .OR. dim_type == 'ZXYHT' ) then
4150  dim1_max = kmax
4151  dim1_s = ks
4152  dim1_e = ke
4153  elseif ( dim_type == 'ZHXYT' ) then
4154  dim1_max = kmax+1
4155  dim1_s = ks-1
4156  dim1_e = ke
4157  elseif( dim_type == 'OXYT' ) then
4158  dim1_max = okmax
4159  dim1_s = oks
4160  dim1_e = oke
4161  elseif( dim_type == 'OHXYT' ) then
4162  dim1_max = okmax+1
4163  dim1_s = oks-1
4164  dim1_e = oke
4165  elseif( dim_type == 'LXYT' ) then
4166  dim1_max = lkmax
4167  dim1_s = lks
4168  dim1_e = lke
4169  elseif( dim_type == 'LHXYT' ) then
4170  dim1_max = lkmax+1
4171  dim1_s = lks-1
4172  dim1_e = lke
4173  elseif( dim_type == 'UXYT' ) then
4174  dim1_max = ukmax
4175  dim1_s = uks
4176  dim1_e = uke
4177  elseif( dim_type == 'UHXYT' ) then
4178  dim1_max = ukmax+1
4179  dim1_s = uks-1
4180  dim1_e = uke
4181  else
4182  log_error("FILE_CARTESC_write_var_4D",*) 'unsupported dimension type. Check! dim_type:', trim(dim_type), ', item:',trim(varname)
4183  call prc_abort
4184  endif
4185 
4186  if ( present(timetarg) ) then
4187  nowtime = timeofs_ + (timetarg-1) * time_interval
4188 
4189  if ( fill_halo_ ) then
4190  do j = js, je
4191  do i = is, ie
4192  do k = 1, dim1_max
4193  varhalo(k,i,j) = var(k,i,j,timetarg)
4194  end do
4195  end do
4196  end do
4197 
4198  ! W halo
4199  do j = 1, ja
4200  do i = 1, is-1
4201  do k = 1, dim1_max
4202  varhalo(k,i,j) = rmiss
4203  enddo
4204  enddo
4205  enddo
4206  ! E halo
4207  do j = 1, ja
4208  do i = ie+1, ia
4209  do k = 1, dim1_max
4210  varhalo(k,i,j) = rmiss
4211  enddo
4212  enddo
4213  enddo
4214  ! S halo
4215  do j = 1, js-1
4216  do i = 1, ia
4217  do k = 1, dim1_max
4218  varhalo(k,i,j) = rmiss
4219  enddo
4220  enddo
4221  enddo
4222  ! N halo
4223  do j = je+1, ja
4224  do i = 1, ia
4225  do k = 1, dim1_max
4226  varhalo(k,i,j) = rmiss
4227  enddo
4228  enddo
4229  enddo
4230 
4231  call file_write( vid, varhalo(dim1_s:dim1_e,dim2_s:dim2_e,dim3_s:dim3_e), &
4232  nowtime, nowtime, start ) ! [IN]
4233  else
4234  call file_write( vid, var(dim1_s:dim1_e,dim2_s:dim2_e,dim3_s:dim3_e,timetarg), &
4235  nowtime, nowtime, start ) ! [IN]
4236  endif
4237  else
4238  nowtime = timeofs_
4239  do n = 1, step
4240  if ( fill_halo_ ) then
4241  do j = js, je
4242  do i = is, ie
4243  do k = 1, dim1_max
4244  varhalo(k,i,j) = var(k,i,j,n)
4245  end do
4246  end do
4247  end do
4248 
4249  ! W halo
4250  do j = 1, ja
4251  do i = 1, is-1
4252  do k = 1, dim1_max
4253  varhalo(k,i,j) = rmiss
4254  enddo
4255  enddo
4256  enddo
4257  ! E halo
4258  do j = 1, ja
4259  do i = ie+1, ia
4260  do k = 1, dim1_max
4261  varhalo(k,i,j) = rmiss
4262  enddo
4263  enddo
4264  enddo
4265  ! S halo
4266  do j = 1, js-1
4267  do i = 1, ia
4268  do k = 1, dim1_max
4269  varhalo(k,i,j) = rmiss
4270  enddo
4271  enddo
4272  enddo
4273  ! N halo
4274  do j = je+1, ja
4275  do i = 1, ia
4276  do k = 1, dim1_max
4277  varhalo(k,i,j) = rmiss
4278  enddo
4279  enddo
4280  enddo
4281 
4282  call file_write( vid, varhalo(dim1_s:dim1_e,dim2_s:dim2_e,dim3_s:dim3_e), &
4283  nowtime, nowtime, start ) ! [IN]
4284  else
4285  call file_write( vid, var(dim1_s:dim1_e,dim2_s:dim2_e,dim3_s:dim3_e,n), &
4286  nowtime, nowtime, start ) ! [IN]
4287  endif
4288  call file_flush( fid )
4289  nowtime = nowtime + time_interval
4290  enddo
4291  endif
4292 
4293  call prof_rapend('FILE_O_NetCDF', 2, disable_barrier = file_single(fid) )
4294 
4295  return
4296  end subroutine file_cartesc_write_var_4d
4297 
4298 
4299  !-----------------------------------------------------------------------------
4300 
4301  ! private procedures
4302 
4303  !-----------------------------------------------------------------------------
4304  subroutine closeall
4305  implicit none
4306 
4307  integer :: fid
4308  !---------------------------------------------------------------------------
4309 
4310  do fid = 0, file_file_max-1
4311  call file_cartesc_close( fid )
4312  enddo
4313 
4314  return
4315  end subroutine closeall
4316 
4317  !-----------------------------------------------------------------------------
4318  subroutine check_1d( &
4319  expected, buffer, &
4320  name )
4321  use scale_prc, only: &
4322  prc_abort
4323  use scale_const, only: &
4324  eps => const_eps
4325  implicit none
4326 
4327  real(RP), intent(in) :: expected(:)
4328  real(RP), intent(in) :: buffer(:)
4329  character(len=*), intent(in) :: name
4330 
4331  real(RP) :: check
4332  integer :: nmax, n
4333 
4334  intrinsic :: size
4335  !---------------------------------------------------------------------------
4336 
4337  nmax = size(expected)
4338  if ( size(buffer) /= nmax ) then
4339  log_error("check_1d",*) 'size of coordinate ('//trim(name)//') is different:', nmax, size(buffer)
4340  call prc_abort
4341  endif
4342 
4343  do n=1, nmax
4344  if ( abs(expected(n)) > eps ) then
4345  check = abs(buffer(n)-expected(n)) / abs(buffer(n)+expected(n)) * 2.0_rp
4346  else
4347  check = abs(buffer(n)-expected(n))
4348  endif
4349 
4350  if ( check > file_cartesc_datacheck_criteria ) then
4351  log_error("check_1d",*) 'value of coordinate ('//trim(name)//') at ', n, ' is different:', &
4352  expected(n), buffer(n), check
4353  call prc_abort
4354  endif
4355  enddo
4356 
4357  return
4358  end subroutine check_1d
4359 
4360  !-----------------------------------------------------------------------------
4361  subroutine check_2d( &
4362  expected, buffer, &
4363  name )
4364  use scale_prc, only: &
4365  prc_abort
4366  use scale_const, only: &
4367  eps => const_eps
4368  implicit none
4369 
4370  real(RP), intent(in) :: expected(:,:)
4371  real(RP), intent(in) :: buffer(:,:)
4372  character(len=*), intent(in) :: name
4373 
4374  real(RP) :: check
4375  integer :: imax, jmax
4376  integer :: i, j
4377 
4378  intrinsic :: size
4379  !---------------------------------------------------------------------------
4380 
4381  imax = size(expected,1)
4382  jmax = size(expected,2)
4383  if ( size(buffer,1) /= imax ) then
4384  log_error("check_2d",*) 'the first size of coordinate ('//trim(name)//') is different:', imax, size(buffer,1)
4385  call prc_abort
4386  endif
4387  if ( size(buffer,2) /= jmax ) then
4388  log_error("check_2d",*) 'the second size of coordinate ('//trim(name)//') is different:', jmax, size(buffer,2)
4389  call prc_abort
4390  endif
4391 
4392  do j=1, jmax
4393  do i=1, imax
4394  if ( abs(expected(i,j)) > eps ) then
4395  check = abs(buffer(i,j)-expected(i,j)) / abs(buffer(i,j)+expected(i,j)) * 2.0_rp
4396  else
4397  check = abs(buffer(i,j)-expected(i,j))
4398  endif
4399 
4400  if ( check > file_cartesc_datacheck_criteria ) then
4401  log_error("check_2d",*) 'value of coordinate ('//trim(name)//') at (', i, ',', j, ') is different:', &
4402  expected(i,j), buffer(i,j), check
4403  call prc_abort
4404  endif
4405  enddo
4406  enddo
4407 
4408  return
4409  end subroutine check_2d
4410 
4411  !-----------------------------------------------------------------------------
4412  subroutine check_3d( &
4413  expected, buffer, &
4414  name, &
4415  transpose )
4416  use scale_prc, only: &
4417  prc_abort
4418  use scale_const, only: &
4419  eps => const_eps
4420  implicit none
4421 
4422  real(RP), intent(in) :: expected(:,:,:)
4423  real(RP), intent(in) :: buffer(:,:,:)
4424  character(len=*), intent(in) :: name
4425  logical, intent(in) :: transpose
4426 
4427  real(RP) :: check
4428  integer :: imax, jmax, kmax
4429  integer :: i, j, k
4430 
4431  intrinsic :: size
4432  !---------------------------------------------------------------------------
4433 
4434  if ( transpose ) then
4435  kmax = size(expected,3)
4436  imax = size(expected,1)
4437  jmax = size(expected,2)
4438  else
4439  kmax = size(expected,1)
4440  imax = size(expected,2)
4441  jmax = size(expected,3)
4442  endif
4443  if ( size(buffer,1) /= kmax ) then
4444  log_error("check_3d",*) 'the first size of coordinate ('//trim(name)//') is different:', kmax, size(buffer,1)
4445  call prc_abort
4446  endif
4447  if ( size(buffer,2) /= imax ) then
4448  log_error("check_3d",*) 'the second size of coordinate ('//trim(name)//') is different:', imax, size(buffer,2)
4449  call prc_abort
4450  endif
4451  if ( size(buffer,3) /= jmax ) then
4452  log_error("check_3d",*) 'the third size of coordinate ('//trim(name)//') is different:', jmax, size(buffer,3)
4453  call prc_abort
4454  endif
4455 
4456  if ( transpose ) then
4457  ! buffer(i,j,k), expected(k,i,j)
4458  do k=1, kmax
4459  do j=1, jmax
4460  do i=1, imax
4461  if ( abs(expected(k,i,j)) > eps ) then
4462  check = abs(buffer(i,j,k)-expected(k,i,j)) / abs(buffer(i,j,k)+expected(k,i,j)) * 2.0_rp
4463  else
4464  check = abs(buffer(i,j,k)-expected(k,i,j))
4465  endif
4466 
4467  if ( check > file_cartesc_datacheck_criteria ) then
4468  log_error("check_3d",*) 'value of coordinate ('//trim(name)//') at ', i, ',', j, ',', k, ' is different:', &
4469  expected(k,i,j), buffer(i,j,k), check
4470  call prc_abort
4471  endif
4472  enddo
4473  enddo
4474  enddo
4475  else
4476  do j=1, jmax
4477  do i=1, imax
4478  do k=1, kmax
4479  if ( abs(expected(k,i,j)) > eps ) then
4480  check = abs(buffer(k,i,j)-expected(k,i,j)) / abs(buffer(k,i,j)+expected(k,i,j)) * 2.0_rp
4481  else
4482  check = abs(buffer(k,i,j)-expected(k,i,j))
4483  endif
4484 
4485  if ( check > file_cartesc_datacheck_criteria ) then
4486  log_error("check_3d",*) 'value of coordinate ('//trim(name)//') at ', k, ',', i, ',', j, ' is different:', &
4487  expected(k,i,j), buffer(k,i,j), check
4488  call prc_abort
4489  endif
4490  enddo
4491  enddo
4492  enddo
4493  endif
4494 
4495  return
4496  end subroutine check_3d
4497 
4498  subroutine set_dimension_informations
4499  use scale_prc_cartesc, only: &
4500  prc_periodic_x, &
4501  prc_periodic_y, &
4502  prc_num_x, &
4503  prc_num_y, &
4504  prc_has_w, &
4505  prc_has_e, &
4506  prc_has_s, &
4507  prc_has_n
4508  implicit none
4509  !---------------------------------------------------------------------------
4510 
4511  ! Dimension Information
4512 
4513  ! 1D variable
4514  call set_dimension( 'Z', 1, 'z', ka )
4515  call set_dimension( 'X', 1, 'x', ia )
4516  call set_dimension( 'Y', 1, 'y', ja )
4517 
4518  ! 2D variable
4519  call set_dimension( 'XY', 2, (/ 'x' , 'y' /), ia*ja, .true., area='cell_area', location='face' )
4520  call set_dimension( 'UY', 2, (/ 'xh', 'y ' /), ia*ja, .true., area='cell_area_uy', location='edge1' )
4521  call set_dimension( 'XV', 2, (/ 'x ', 'yh' /), ia*ja, .true., area='cell_area_xv', location='edge2' )
4522  call set_dimension( 'UV', 2, (/ 'xh', 'yh' /), ia*ja, .true., location='node' )
4523 
4524  call set_dimension( 'ZX', 2, (/ 'z', 'x' /), ka*ia )
4525  call set_dimension( 'ZY', 2, (/ 'z', 'y' /), ka*ja )
4526 
4527  ! 3D variable
4528  call set_dimension( 'ZXY', 3, (/ 'z', 'x', 'y' /), ka*ia*ja, .true., &
4529  area='cell_area', area_x='cell_area_zxy_x', area_y='cell_area_zxy_y', &
4530  volume='cell_volume', location='face' )
4531  call set_dimension( 'ZHXY', 3, (/ 'zh', 'x ', 'y ' /), (ka+1)*ia*ja, .true., &
4532  area='cell_area', area_x='cell_area_wxy_x', area_y='cell_area_wxy_y', &
4533  volume='cell_volume_wxy', location='face' )
4534  call set_dimension( 'ZXHY', 3, (/ 'z ', 'xh', 'y ' /), ka*ia*ja, .true., &
4535  area='cell_area_uy', area_x='cell_area_zuy_x', &
4536  volume='cell_volume_zuy', location='edge1' )
4537  call set_dimension( 'ZXYH', 3, (/ 'z ', 'x ', 'yh' /), ka*ia*ja, .true., &
4538  area='cell_area_xv', area_y='cell_area_zxv_y', &
4539  volume='cell_volume_zxv', location='edge2' )
4540  call set_dimension( 'ZXHYH', 3, (/ 'z ', 'xh', 'yh' /), ka*ia*ja, .true., &
4541  area_x='cell_area_zuv_x', area_y='cell_area_zuv_y', &
4542  location='node' )
4543  call set_dimension( 'ZHXHY', 3, (/ 'zh', 'xh', 'y ' /), (ka+1)*ia*ja, .true., &
4544  area_x='cell_area_wuy_x', &
4545  location='edge1' )
4546  call set_dimension( 'ZHXYH', 3, (/ 'zh', 'x ', 'yh' /), (ka+1)*ia*ja, .true., &
4547  area_y='cell_area_wxv_y', &
4548  location='edge2' )
4549 
4550  if ( okmax > 0 ) then
4551  call set_dimension( 'OXY', 3, (/ 'oz', 'x ', 'y ' /), okmax*ia*ja, .true., area='cell_area', volume='cell_volume_oxy', location='face', grid='ocean' )
4552  call set_dimension( 'OHXY', 3, (/ 'ozh', 'x ', 'y ' /), (okmax+1)*ia*ja, .true., area='cell_area', volume='cell_volume_oxy', location='face', grid='ocean' )
4553  end if
4554  if ( lkmax > 0 ) then
4555  call set_dimension( 'LXY', 3, (/ 'lz', 'x ', 'y ' /), lkmax*ia*ja, .true., area='cell_area', volume='cell_volume_lxy', location='face', grid='land' )
4556  call set_dimension( 'LHXY', 3, (/ 'lzh', 'x ', 'y ' /), (lkmax+1)*ia*ja, .true., area='cell_area', volume='cell_volume_lxy', location='face', grid='land' )
4557  end if
4558  if ( ukmax > 0 ) then
4559  call set_dimension( 'UXY', 3, (/ 'uz', 'x ', 'y ' /), ukmax*ia*ja, .true., area='cell_area', volume='cell_volume_uxy', location='face', grid='urban' )
4560  call set_dimension( 'UHXY', 3, (/ 'uzh', 'x ', 'y ' /), (ukmax+1)*ia*ja, .true., area='cell_area', volume='cell_volume_uxy', location='face', grid='urban' )
4561  end if
4562 
4563 
4564  ! Axis information
4565 
4566  if ( prc_periodic_x ) then
4567  file_cartesc_axis_info(1)%periodic = .true.
4568  file_cartesc_axis_info(2)%periodic = .true.
4569  else
4570  file_cartesc_axis_info(1)%periodic = .false.
4571  file_cartesc_axis_info(2)%periodic = .false.
4572  endif
4573 
4574  if ( prc_periodic_y ) then
4575  file_cartesc_axis_info(3)%periodic = .true.
4576  file_cartesc_axis_info(4)%periodic = .true.
4577  else
4578  file_cartesc_axis_info(3)%periodic = .false.
4579  file_cartesc_axis_info(4)%periodic = .false.
4580  endif
4581 
4582 
4583  ! for x
4584  if ( prc_periodic_x ) then
4585  file_cartesc_axis_info(1)%size_global (1) = imax * prc_num_x
4586  file_cartesc_axis_info(1)%start_global(1) = is_ing - ihalo
4587  file_cartesc_axis_info(1)%halo_global (1) = 0 ! west side
4588  file_cartesc_axis_info(1)%halo_global (2) = 0 ! east side
4589  file_cartesc_axis_info(1)%halo_local (1) = 0 ! west side
4590  file_cartesc_axis_info(1)%halo_local (2) = 0 ! east side
4591  else
4592  file_cartesc_axis_info(1)%size_global (1) = iag
4593  file_cartesc_axis_info(1)%start_global(1) = isga
4594  file_cartesc_axis_info(1)%halo_global (1) = ihalo ! west side
4595  file_cartesc_axis_info(1)%halo_global (2) = ihalo ! east side
4596  file_cartesc_axis_info(1)%halo_local (1) = ihalo ! west side
4597  file_cartesc_axis_info(1)%halo_local (2) = ihalo ! east side
4598  if( prc_has_w ) file_cartesc_axis_info(1)%halo_local(1) = 0
4599  if( prc_has_e ) file_cartesc_axis_info(1)%halo_local(2) = 0
4600  endif
4601  ! for xh
4602  file_cartesc_axis_info(2) = file_cartesc_axis_info(1)
4603 
4604  ! for y
4605  if ( prc_periodic_y ) then
4606  file_cartesc_axis_info(3)%size_global (1) = jmax * prc_num_y
4607  file_cartesc_axis_info(3)%start_global(1) = js_ing - jhalo
4608  file_cartesc_axis_info(3)%halo_global (1) = 0 ! south side
4609  file_cartesc_axis_info(3)%halo_global (2) = 0 ! north side
4610  file_cartesc_axis_info(3)%halo_local (1) = 0 ! south side
4611  file_cartesc_axis_info(3)%halo_local (2) = 0 ! north side
4612  else
4613  file_cartesc_axis_info(3)%size_global (1) = jag
4614  file_cartesc_axis_info(3)%start_global(1) = jsga
4615  file_cartesc_axis_info(3)%halo_global (1) = jhalo ! south side
4616  file_cartesc_axis_info(3)%halo_global (2) = jhalo ! north side
4617  file_cartesc_axis_info(3)%halo_local (1) = jhalo ! south side
4618  file_cartesc_axis_info(3)%halo_local (2) = jhalo ! north side
4619  if( prc_has_s ) file_cartesc_axis_info(3)%halo_local(1) = 0
4620  if( prc_has_n ) file_cartesc_axis_info(3)%halo_local(2) = 0
4621  endif
4622  ! for yh
4623  file_cartesc_axis_info(4) = file_cartesc_axis_info(3)
4624 
4625 
4626  return
4627  end subroutine set_dimension_informations
4628 
4629  subroutine set_dimension( name, ndims, dims, size, mapping, area, area_x, area_y, volume, location, grid )
4630  use scale_prc, only: &
4631  prc_abort
4632  character(len=*), intent(in) :: name
4633  integer, intent(in) :: ndims
4634  character(len=*), intent(in) :: dims(ndims)
4635  integer, intent(in) :: size
4636  logical, intent(in), optional :: mapping
4637  character(len=*), intent(in), optional :: area
4638  character(len=*), intent(in), optional :: area_x
4639  character(len=*), intent(in), optional :: area_y
4640  character(len=*), intent(in), optional :: volume
4641  character(len=*), intent(in), optional :: location
4642  character(len=*), intent(in), optional :: grid
4643 
4644  integer, save :: dimid = 0
4645 
4646  integer :: n
4647 
4648  do n = 1, 2
4649  dimid = dimid + 1
4650  if ( dimid > file_cartesc_ndims ) then
4651  log_error("set_dimension",*) 'number of dimensions exceeds the limit', dimid, file_cartesc_ndims
4652  call prc_abort
4653  end if
4654 
4655  if ( n==1 ) then
4656  file_cartesc_dims(dimid)%name = name
4657  else
4658  file_cartesc_dims(dimid)%name = trim(name)//"T"
4659  end if
4660  file_cartesc_dims(dimid)%ndims = ndims
4661  file_cartesc_dims(dimid)%dims(1:ndims) = dims(:)
4662  file_cartesc_dims(dimid)%size = size
4663 
4664  if ( present(mapping) ) then
4665  file_cartesc_dims(dimid)%mapping = mapping
4666  else
4667  file_cartesc_dims(dimid)%mapping = .false.
4668  end if
4669 
4670  if ( present(area) ) then
4671  file_cartesc_dims(dimid)%area = area
4672  else
4673  file_cartesc_dims(dimid)%area = ''
4674  end if
4675  if ( present(area_x) ) then
4676  file_cartesc_dims(dimid)%area = area_x
4677  else
4678  file_cartesc_dims(dimid)%area = ''
4679  end if
4680  if ( present(area_y) ) then
4681  file_cartesc_dims(dimid)%area = area_y
4682  else
4683  file_cartesc_dims(dimid)%area = ''
4684  end if
4685 
4686  if ( present(volume) ) then
4687  file_cartesc_dims(dimid)%volume = volume
4688  else
4689  file_cartesc_dims(dimid)%volume = ''
4690  end if
4691 
4692  if ( present(location) ) then
4693  file_cartesc_dims(dimid)%location = location
4694  if ( present(grid) ) then
4695  file_cartesc_dims(dimid)%grid = 'grid_'//trim(grid)
4696  else
4697  file_cartesc_dims(dimid)%grid = 'grid'
4698  end if
4699  else
4700  file_cartesc_dims(dimid)%location = ''
4701  file_cartesc_dims(dimid)%grid = ''
4702  end if
4703 
4704  end do
4705 
4706  return
4707  end subroutine set_dimension
4708 
4709  !-----------------------------------------------------------------------------
4711  subroutine construct_derived_datatype
4712  use mpi
4713  use scale_prc_cartesc, only: &
4714  prc_num_x, &
4715  prc_num_y
4716  implicit none
4717 
4718  integer :: err, order
4719  integer :: sizes(3), subsizes(3), sub_off(3)
4720  !---------------------------------------------------------------------------
4721 
4722  order = mpi_order_fortran
4723 
4724  centertypexy = mpi_datatype_null
4725  centertypezx = mpi_datatype_null
4726  centertypezxy = mpi_datatype_null
4727  centertypezhxy = mpi_datatype_null
4728  centertypeocean = mpi_datatype_null
4729  centertypeland = mpi_datatype_null
4730  centertypeurban = mpi_datatype_null
4731 
4732  etype = mpi_float
4733 
4734  if( rp == 8 ) etype = mpi_double
4735 
4736  ! for dim_type == 'XY'
4737  startxy(1) = is_ing - ihalo
4738  startxy(2) = js_ing - jhalo
4739  countxy(1) = ia
4740  countxy(2) = ja
4741  ! for dim_type == 'ZXY'
4742  startzxy(1) = 1
4743  startzxy(2:3) = startxy(1:2)
4744  countzxy(1) = kmax
4745  countzxy(2:3) = countxy(1:2)
4746  ! construct MPI subarray data type
4747  sizes(1) = ka
4748  sizes(2) = ia
4749  sizes(3) = ja
4750  subsizes(1) = kmax
4751  subsizes(2) = ia
4752  subsizes(3) = ja
4753  sub_off(1) = ks - 1 ! MPI start index starts with 0
4754  sub_off(2) = 0
4755  sub_off(3) = 0
4756  call mpi_type_create_subarray(3, sizes, subsizes, sub_off, order, etype, centertypezxy, err)
4757  call mpi_type_commit(centertypezxy, err)
4758 
4759  ! for dim_type == 'ZHXY'
4760  startzhxy(1) = 1
4761  startzhxy(2:3) = startxy(1:2)
4762  countzhxy(1) = kmax+1
4763  countzhxy(2:3) = countxy(1:2)
4764  ! construct MPI subarray data type
4765  sizes(1) = ka
4766  sizes(2) = ia
4767  sizes(3) = ja
4768  subsizes(1) = kmax+1
4769  subsizes(2) = ia
4770  subsizes(3) = ja
4771  sub_off(1) = ks - 2 ! MPI start index starts with 0
4772  sub_off(2) = 0
4773  sub_off(3) = 0
4774  call mpi_type_create_subarray(3, sizes, subsizes, sub_off, order, etype, centertypezhxy, err)
4775  call mpi_type_commit(centertypezhxy, err)
4776 
4777  if ( okmax > 0 ) then
4778  ! for dim_type == 'OXY'
4779  startocean(1) = 1
4780  startocean(2:3) = startxy(1:2)
4781  countocean(1) = okmax
4782  countocean(2:3) = countxy(1:2)
4783  ! construct MPI subarray data type
4784  sizes(1) = okmax
4785  subsizes(1) = okmax
4786  sub_off(1) = oks - 1 ! MPI start index starts with 0
4787  call mpi_type_create_subarray(3, sizes, subsizes, sub_off, order, etype, centertypeocean, err)
4788  call mpi_type_commit(centertypeocean, err)
4789  end if
4790 
4791  if ( lkmax > 0 ) then
4792  ! for dim_type == 'LXY'
4793  startland(1) = 1
4794  startland(2:3) = startxy(1:2)
4795  countland(1) = lkmax
4796  countland(2:3) = countxy(1:2)
4797  ! construct MPI subarray data type
4798  sizes(1) = lkmax
4799  subsizes(1) = lkmax
4800  sub_off(1) = lks - 1 ! MPI start index starts with 0
4801  call mpi_type_create_subarray(3, sizes, subsizes, sub_off, order, etype, centertypeland, err)
4802  call mpi_type_commit(centertypeland, err)
4803  end if
4804 
4805  if ( ukmax > 0 ) then
4806  ! for dim_type == 'UXY'
4807  starturban(1) = 1
4808  starturban(2:3) = startxy(1:2)
4809  counturban(1) = ukmax
4810  counturban(2:3) = countxy(1:2)
4811  ! construct MPI subarray data type
4812  sizes(1) = ukmax
4813  subsizes(1) = ukmax
4814  sub_off(1) = uks - 1 ! MPI start index starts with 0
4815  call mpi_type_create_subarray(3, sizes, subsizes, sub_off, order, etype, centertypeurban, err)
4816  call mpi_type_commit(centertypeurban, err)
4817  end if
4818 
4819  ! for dim_type == 'ZX'
4820  startzx(1) = khalo+1
4821  startzx(2) = is_ing - ihalo
4822  countzx(1) = kmax
4823  countzx(2) = ia
4824  ! construct MPI subarray data type
4825  sizes(1) = ka
4826  sizes(2) = ia
4827  subsizes(1) = kmax
4828  subsizes(2) = imaxb
4829  sub_off(1) = khalo ! MPI start index starts with 0
4830  sub_off(2) = isb - 1 ! MPI start index starts with 0
4831  call mpi_type_create_subarray(2, sizes, subsizes, sub_off, order, etype, centertypezx, err)
4832  call mpi_type_commit(centertypezx, err)
4833 
4834  return
4835  end subroutine construct_derived_datatype
4836 
4837  !-----------------------------------------------------------------------------
4839  subroutine free_derived_datatype
4840  use mpi
4841  implicit none
4842 
4843  integer :: err
4844  !---------------------------------------------------------------------------
4845 
4846  if( centertypexy /= mpi_datatype_null ) call mpi_type_free(centertypexy, err)
4847  if( centertypezx /= mpi_datatype_null ) call mpi_type_free(centertypezx, err)
4848  if( centertypezxy /= mpi_datatype_null ) call mpi_type_free(centertypezxy, err)
4849  if( centertypezhxy /= mpi_datatype_null ) call mpi_type_free(centertypezhxy, err)
4850  if( centertypeocean /= mpi_datatype_null ) call mpi_type_free(centertypeocean, err)
4851  if( centertypeland /= mpi_datatype_null ) call mpi_type_free(centertypeland, err)
4852  if( centertypeurban /= mpi_datatype_null ) call mpi_type_free(centertypeurban, err)
4853 
4854  return
4855  end subroutine free_derived_datatype
4856 
4857 end module scale_file_cartesc
scale_atmos_grid_cartesc_index::isb
integer, public isb
Definition: scale_atmos_grid_cartesC_index.F90:63
scale_file_cartesc::file_cartesc_set_coordinates_land
subroutine, public file_cartesc_set_coordinates_land(VOL)
set volume for land
Definition: scale_file_cartesC.F90:557
scale_urban_grid_cartesc_index::uja
integer, public uja
Definition: scale_urban_grid_cartesC_index.F90:44
scale_atmos_grid_cartesc_index::ke
integer, public ke
end point of inner domain: z, local
Definition: scale_atmos_grid_cartesC_index.F90:52
scale_file_cartesc::file_cartesc_read_1d
subroutine file_cartesc_read_1d(basename, varname, dim_type, var, step, aggregate, allow_missing)
interface FILE_CARTESC_read Read data from file This routine is a wrapper of the lower primitive rout...
Definition: scale_file_cartesC.F90:1067
scale_time::time_nowdaysec
real(dp), public time_nowdaysec
second of current time [sec]
Definition: scale_time.F90:70
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:342
scale_ocean_grid_cartesc::ocean_grid_cartesc_cz
real(rp), dimension(:), allocatable, public ocean_grid_cartesc_cz
center coordinate [m]: z, local=global
Definition: scale_ocean_grid_cartesC.F90:35
scale_urban_grid_cartesc::urban_grid_cartesc_cdz
real(rp), dimension(:), allocatable, public urban_grid_cartesc_cdz
z-length of control volume [m]
Definition: scale_urban_grid_cartesC.F90:37
scale_land_grid_cartesc_index::lia
integer, public lia
Definition: scale_land_grid_cartesC_index.F90:37
scale_atmos_grid_cartesc::atmos_grid_cartesc_cdz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdz
z-length of control volume [m]
Definition: scale_atmos_grid_cartesC.F90:42
scale_urban_grid_cartesc_index::uia
integer, public uia
Definition: scale_urban_grid_cartesC_index.F90:40
scale_ocean_grid_cartesc_index::oke
integer, public oke
Definition: scale_ocean_grid_cartesC_index.F90:38
scale_atmos_grid_cartesc_index::ihalo
integer, public ihalo
Definition: scale_atmos_grid_cartesC_index.F90:44
scale_atmos_grid_cartesc_index::jmaxb
integer, public jmaxb
Definition: scale_atmos_grid_cartesC_index.F90:62
scale_prc_cartesc::prc_has_s
logical, public prc_has_s
Definition: scale_prc_cartesC.F90:50
scale_land_grid_cartesc_index::lja
integer, public lja
Definition: scale_land_grid_cartesC_index.F90:38
scale_file_cartesc::file_cartesc_enddef
subroutine, public file_cartesc_enddef(fid)
Exit netCDF file define mode.
Definition: scale_file_cartesC.F90:943
scale_file_h::file_real4
integer, parameter, public file_real4
Definition: scale_file_h.F90:24
scale_land_grid_cartesc::land_grid_cartesc_cdz
real(rp), dimension(:), allocatable, public land_grid_cartesc_cdz
z-length of control volume [m]
Definition: scale_land_grid_cartesC.F90:36
scale_file::file_enddef
subroutine, public file_enddef(fid)
Definition: scale_file.F90:4585
scale_calendar::calendar_get_name
subroutine, public calendar_get_name(name)
Definition: scale_calendar.F90:715
scale_file_cartesc::file_cartesc_def_var
subroutine, public file_cartesc_def_var(fid, varname, desc, unit, dim_type, datatype, vid, standard_name, timeintv, nsteps, cell_measures)
Define a variable to file.
Definition: scale_file_cartesC.F90:3307
scale_file_cartesc::set_dimension
subroutine set_dimension(name, ndims, dims, size, mapping, area, area_x, area_y, volume, location, grid)
Definition: scale_file_cartesC.F90:4630
scale_file_cartesc::file_cartesc_write_1d
subroutine file_cartesc_write_1d(var, basename, title, varname, desc, unit, dim_type, datatype, date, subsec, append, aggregate, standard_name, cell_measures)
interface FILE_CARTESC_write Write data to file This routine is a wrapper of the lowere primitive rou...
Definition: scale_file_cartesC.F90:2000
scale_prc_cartesc::prc_periodic_y
logical, public prc_periodic_y
periodic condition or not (Y)?
Definition: scale_prc_cartesC.F90:53
scale_precision
module PRECISION
Definition: scale_precision.F90:14
scale_atmos_grid_cartesc_index::ka
integer, public ka
Definition: scale_atmos_grid_cartesC_index.F90:47
scale_atmos_grid_cartesc_index::isga
integer, public isga
start point of the full domain: cx, global
Definition: scale_atmos_grid_cartesC_index.F90:81
scale_file_cartesc::file_cartesc_put_globalattributes
subroutine, public file_cartesc_put_globalattributes(fid, prc_rank_x, prc_rank_y, prc_num_x, prc_num_y, prc_periodic_x, prc_periodic_y, kmax, okmax, lkmax, ukmax, imaxg, jmaxg, khalo, ihalo, jhalo, time, tunits, calendar)
put global attributes
Definition: scale_file_cartesC.F90:2292
scale_file::file_attach_buffer
subroutine, public file_attach_buffer(fid, buf_amount)
Definition: scale_file.F90:4643
scale_file_cartesc::file_cartesc_write_var_3d
subroutine file_cartesc_write_var_3d(fid, vid, var, varname, dim_type, fill_halo)
Write 3D data to file.
Definition: scale_file_cartesC.F90:3727
scale_file::file_flush
subroutine, public file_flush(fid)
Definition: scale_file.F90:4709
scale_land_grid_cartesc_index::lkmax
integer, public lkmax
Definition: scale_land_grid_cartesC_index.F90:32
scale_atmos_grid_cartesc::atmos_grid_cartesc_cdyg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdyg
center coordinate [m]: y, global
Definition: scale_atmos_grid_cartesC.F90:81
scale_const::const_eps
real(rp), public const_eps
small number
Definition: scale_const.F90:33
scale_time::time_nowsubsec
real(dp), public time_nowsubsec
subsecond part of current time [sec]
Definition: scale_time.F90:69
scale_prof::prof_rapstart
subroutine, public prof_rapstart(rapname_base, level, disable_barrier)
Start raptime.
Definition: scale_prof.F90:159
scale_file_cartesc::file_cartesc_set_coordinates_urban
subroutine, public file_cartesc_set_coordinates_urban(VOL)
set volume for urban
Definition: scale_file_cartesC.F90:571
scale_atmos_grid_cartesc::atmos_grid_cartesc_fyg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fyg
face coordinate [m]: y, global
Definition: scale_atmos_grid_cartesC.F90:78
scale_atmos_grid_cartesc::atmos_grid_cartesc_cdy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdy
y-length of control volume [m]
Definition: scale_atmos_grid_cartesC.F90:61
scale_ocean_grid_cartesc_index::oka
integer, public oka
Definition: scale_ocean_grid_cartesC_index.F90:36
scale_atmos_grid_cartesc::atmos_grid_cartesc_fx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fx
face coordinate [m]: x, local
Definition: scale_atmos_grid_cartesC.F90:57
scale_atmos_grid_cartesc::atmos_grid_cartesc_fdyg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdyg
center coordinate [m]: y, global
Definition: scale_atmos_grid_cartesC.F90:83
scale_file_h::file_rmiss
real(dp), parameter, public file_rmiss
Definition: scale_file_h.F90:49
scale_prc::prc_myrank
integer, public prc_myrank
process num in local communicator
Definition: scale_prc.F90:90
scale_atmos_grid_cartesc::atmos_grid_cartesc_fdy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdy
y-length of grid(j+1) to grid(j) [m]
Definition: scale_atmos_grid_cartesC.F90:63
scale_ocean_grid_cartesc_index::okmax
integer, public okmax
Definition: scale_ocean_grid_cartesC_index.F90:32
scale_atmos_grid_cartesc_index::khalo
integer, parameter, public khalo
Definition: scale_atmos_grid_cartesC_index.F90:43
scale_atmos_grid_cartesc::atmos_grid_cartesc_fbfx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fbfx
face buffer factor (0-1): x
Definition: scale_atmos_grid_cartesC.F90:72
scale_file::file_opened
logical function, public file_opened(fid)
check if the file is opened?
Definition: scale_file.F90:527
scale_calendar
module CALENDAR
Definition: scale_calendar.F90:13
scale_urban_grid_cartesc_index
module urban / grid / icosahedralA / index
Definition: scale_urban_grid_cartesC_index.F90:11
scale_atmos_grid_cartesc_index::imaxg
integer, public imaxg
Definition: scale_atmos_grid_cartesC_index.F90:71
scale_atmos_grid_cartesc_index::je_ing
integer, public je_ing
end point of the inner domain: cy, global
Definition: scale_atmos_grid_cartesC_index.F90:80
scale_ocean_grid_cartesc
module ocean / grid / cartesianC
Definition: scale_ocean_grid_cartesC.F90:12
scale_io::h_institute
character(len=h_mid), public h_institute
for file header
Definition: scale_io.F90:51
scale_atmos_grid_cartesc::atmos_grid_cartesc_cdxg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdxg
center coordinate [m]: x, global
Definition: scale_atmos_grid_cartesC.F90:80
scale_urban_grid_cartesc::urban_grid_cartesc_cz
real(rp), dimension(:), allocatable, public urban_grid_cartesc_cz
center coordinate [m]: z, local=global
Definition: scale_urban_grid_cartesC.F90:35
scale_file
module file
Definition: scale_file.F90:15
scale_atmos_grid_cartesc_index::imax
integer, public imax
Definition: scale_atmos_grid_cartesC_index.F90:37
scale_io::h_source
character(len=h_mid), public h_source
for file header
Definition: scale_io.F90:50
scale_file_cartesc::file_cartesc_def_axes
subroutine file_cartesc_def_axes(fid, dtype, hasZ)
define axis variables in the file
Definition: scale_file_cartesC.F90:2356
scale_atmos_grid_cartesc_index::jmaxg
integer, public jmaxg
Definition: scale_atmos_grid_cartesC_index.F90:72
scale_prc_cartesc::prc_has_n
logical, public prc_has_n
Definition: scale_prc_cartesC.F90:48
scale_land_grid_cartesc_index
module land / grid / cartesianC / index
Definition: scale_land_grid_cartesC_index.F90:11
scale_atmos_grid_cartesc_index::jeb
integer, public jeb
Definition: scale_atmos_grid_cartesC_index.F90:66
scale_file_cartesc::axisattinfo
Definition: scale_file_cartesC.F90:96
scale_file::file_def_axis
subroutine, public file_def_axis(fid, name, desc, units, dim_name, dtype, dim_size, bounds)
Definition: scale_file.F90:667
scale_prc_cartesc::prc_has_e
logical, public prc_has_e
Definition: scale_prc_cartesC.F90:49
scale_urban_grid_cartesc_index::ukmax
integer, public ukmax
Definition: scale_urban_grid_cartesC_index.F90:32
scale_atmos_grid_cartesc::atmos_grid_cartesc_cbfx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cbfx
center buffer factor (0-1): x
Definition: scale_atmos_grid_cartesC.F90:70
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_precision::rp
integer, parameter, public rp
Definition: scale_precision.F90:41
scale_mapprojection
module Map projection
Definition: scale_mapprojection.F90:12
scale_file_cartesc::file_cartesc_read_auto_3d
subroutine file_cartesc_read_auto_3d(fid, varname, var, step, existed)
Read 3D data from file.
Definition: scale_file_cartesC.F90:1866
scale_atmos_grid_cartesc_index::ie
integer, public ie
end point of inner domain: x, local
Definition: scale_atmos_grid_cartesC_index.F90:54
scale_atmos_grid_cartesc::atmos_grid_cartesc_fbfxg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fbfxg
face buffer factor (0-1): x, global
Definition: scale_atmos_grid_cartesC.F90:87
scale_io
module STDIO
Definition: scale_io.F90:10
scale_atmos_grid_cartesc_index::jag
integer, public jag
Definition: scale_atmos_grid_cartesC_index.F90:74
scale_file_cartesc::file_cartesc_get_size_id
subroutine file_cartesc_get_size_id(fid, KMAX, OKMAX, LKMAX, UKMAX, IMAXG, JMAXG, KHALO, IHALO, JHALO)
Definition: scale_file_cartesC.F90:399
scale_atmos_grid_cartesc_index::iag
integer, public iag
Definition: scale_atmos_grid_cartesC_index.F90:73
scale_prc_cartesc::prc_periodic_x
logical, public prc_periodic_x
periodic condition or not (X)?
Definition: scale_prc_cartesC.F90:52
scale_atmos_grid_cartesc_index::js_ing
integer, public js_ing
start point of the inner domain: cy, global
Definition: scale_atmos_grid_cartesC_index.F90:79
scale_atmos_grid_cartesc::atmos_grid_cartesc_cbfz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cbfz
center buffer factor (0-1): z
Definition: scale_atmos_grid_cartesC.F90:46
scale_file::file_close
subroutine, public file_close(fid, abort)
Definition: scale_file.F90:4738
scale_ocean_grid_cartesc::ocean_grid_cartesc_fz
real(rp), dimension(:), allocatable, public ocean_grid_cartesc_fz
face coordinate [m]: z, local=global
Definition: scale_ocean_grid_cartesC.F90:36
scale_atmos_grid_cartesc::atmos_grid_cartesc_cxg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cxg
center coordinate [m]: x, global
Definition: scale_atmos_grid_cartesC.F90:75
scale_file_cartesc::file_cartesc_read_var_2d
subroutine file_cartesc_read_var_2d(fid, varname, dim_type, var, step, allow_missing)
Read 2D data from file.
Definition: scale_file_cartesC.F90:1350
scale_ocean_grid_cartesc_index::oja
integer, public oja
Definition: scale_ocean_grid_cartesC_index.F90:44
scale_file::file_def_associatedcoordinate
subroutine, public file_def_associatedcoordinate(fid, name, desc, units, dim_names, dtype)
Definition: scale_file.F90:1037
scale_atmos_grid_cartesc_index
module atmosphere / grid / cartesC index
Definition: scale_atmos_grid_cartesC_index.F90:12
scale_const
module CONSTANT
Definition: scale_const.F90:11
scale_file_cartesc::file_cartesc_read_var_3d
subroutine file_cartesc_read_var_3d(fid, varname, dim_type, var, step, allow_missing)
Read 3D data from file.
Definition: scale_file_cartesC.F90:1450
scale_atmos_grid_cartesc_index::ia
integer, public ia
Definition: scale_atmos_grid_cartesC_index.F90:48
scale_file_cartesc::file_cartesc_set_coordinates_ocean
subroutine, public file_cartesc_set_coordinates_ocean(VOL)
set volume for ocean
Definition: scale_file_cartesC.F90:543
scale_atmos_grid_cartesc::atmos_grid_cartesc_fbfy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fbfy
face buffer factor (0-1): y
Definition: scale_atmos_grid_cartesC.F90:73
scale_atmos_grid_cartesc_index::ie_ing
integer, public ie_ing
end point of the inner domain: cx, global
Definition: scale_atmos_grid_cartesC_index.F90:78
scale_prc_cartesc::prc_2drank
integer, dimension(:,:), allocatable, public prc_2drank
node index in 2D topology
Definition: scale_prc_cartesC.F90:44
scale_atmos_grid_cartesc_index::kmax
integer, public kmax
Definition: scale_atmos_grid_cartesC_index.F90:36
scale_file_cartesc::construct_derived_datatype
subroutine construct_derived_datatype
construct MPI derived datatypes for read buffers
Definition: scale_file_cartesC.F90:4712
scale_urban_grid_cartesc
module urban / grid / cartesianC
Definition: scale_urban_grid_cartesC.F90:12
scale_atmos_grid_cartesc_index::is_ing
integer, public is_ing
start point of the inner domain: cx, global
Definition: scale_atmos_grid_cartesC_index.F90:77
scale_atmos_grid_cartesc::atmos_grid_cartesc_fy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fy
face coordinate [m]: y, local
Definition: scale_atmos_grid_cartesC.F90:58
scale_file::file_open
subroutine, public file_open(basename, fid, mode, single, aggregate, rankid, postfix)
Definition: scale_file.F90:487
scale_file_cartesc::file_cartesc_close
subroutine, public file_cartesc_close(fid)
Close a netCDF file.
Definition: scale_file_cartesC.F90:1023
scale_prc_cartesc
module process / cartesC
Definition: scale_prc_cartesC.F90:11
scale_atmos_grid_cartesc::atmos_grid_cartesc_fbfz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fbfz
face buffer factor (0-1): z
Definition: scale_atmos_grid_cartesC.F90:47
scale_file_cartesc::file_cartesc_write_axes
subroutine file_cartesc_write_axes(fid, haszcoord, start)
write axis to the file
Definition: scale_file_cartesC.F90:2839
scale_ocean_grid_cartesc::ocean_grid_cartesc_cdz
real(rp), dimension(:), allocatable, public ocean_grid_cartesc_cdz
z-length of control volume [m]
Definition: scale_ocean_grid_cartesC.F90:37
scale_prof
module profiler
Definition: scale_prof.F90:11
scale_file_cartesc::file_cartesc_cleanup
subroutine, public file_cartesc_cleanup
deallocate buffers
Definition: scale_file_cartesC.F90:314
scale_atmos_grid_cartesc_index::is
integer, public is
start point of inner domain: x, local
Definition: scale_atmos_grid_cartesC_index.F90:53
scale_atmos_grid_cartesc_index::jhalo
integer, public jhalo
Definition: scale_atmos_grid_cartesC_index.F90:45
scale_file_cartesc::file_cartesc_read_var_4d
subroutine file_cartesc_read_var_4d(fid, varname, dim_type, step, var, allow_missing)
Read 4D data from file.
Definition: scale_file_cartesC.F90:1629
scale_ocean_grid_cartesc_index
module ocean / grid / cartesianC / index
Definition: scale_ocean_grid_cartesC_index.F90:11
scale_precision::dp
integer, parameter, public dp
Definition: scale_precision.F90:32
scale_atmos_grid_cartesc::atmos_grid_cartesc_cbfxg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cbfxg
center buffer factor (0-1): x, global
Definition: scale_atmos_grid_cartesC.F90:85
scale_file_cartesc::file_cartesc_write_var_4d
subroutine file_cartesc_write_var_4d(fid, vid, var, varname, dim_type, timeintv, timetarg, timeofs, fill_halo)
Write 4D data to file.
Definition: scale_file_cartesC.F90:4070
scale_file_h
module file_h
Definition: scale_file_h.F90:11
scale_atmos_grid_cartesc_index::ja
integer, public ja
Definition: scale_atmos_grid_cartesC_index.F90:49
scale_time
module TIME
Definition: scale_time.F90:11
scale_file::file_add_associatedvariable
subroutine, public file_add_associatedvariable(fid, vname, existed)
Definition: scale_file.F90:422
scale_file_cartesc::set_dimension_informations
subroutine set_dimension_informations
Definition: scale_file_cartesC.F90:4499
scale_atmos_grid_cartesc::atmos_grid_cartesc_fdx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdx
x-length of grid(i+1) to grid(i) [m]
Definition: scale_atmos_grid_cartesC.F90:62
scale_land_grid_cartesc::land_grid_cartesc_cz
real(rp), dimension(:), allocatable, public land_grid_cartesc_cz
center coordinate [m]: z, local=global
Definition: scale_land_grid_cartesC.F90:34
scale_file_cartesc::file_cartesc_set_coordinates_atmos
subroutine, public file_cartesc_set_coordinates_atmos(CZ, FZ, LON, LONUY, LONXV, LONUV, LAT, LATUY, LATXV, LATUV, TOPO, LSMASK)
set latlon and z for atmosphere
Definition: scale_file_cartesC.F90:454
scale_file_cartesc::file_cartesc_set_areavol_atmos
subroutine, public file_cartesc_set_areavol_atmos(AREA, AREAZUY_X, AREAZXV_Y, AREAWUY_X, AREAWXV_Y, AREAUY, AREAZXY_X, AREAZUV_Y, AREAXV, AREAZUV_X, AREAZXY_Y, VOL, VOLWXY, VOLZUY, VOLZXV)
set area and volume
Definition: scale_file_cartesC.F90:500
scale_atmos_grid_cartesc::atmos_grid_cartesc_fbfyg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fbfyg
face buffer factor (0-1): y, global
Definition: scale_atmos_grid_cartesC.F90:88
scale_urban_grid_cartesc_index::uks
integer, public uks
Definition: scale_urban_grid_cartesC_index.F90:37
scale_atmos_grid_cartesc::atmos_grid_cartesc_fxg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fxg
face coordinate [m]: x, global
Definition: scale_atmos_grid_cartesC.F90:77
scale_file::file_single
logical function, public file_single(fid)
check if the file is single
Definition: scale_file.F90:544
scale_atmos_grid_cartesc_index::ks
integer, public ks
start point of inner domain: z, local
Definition: scale_atmos_grid_cartesC_index.F90:51
scale_atmos_grid_cartesc_index::imaxb
integer, public imaxb
Definition: scale_atmos_grid_cartesC_index.F90:61
scale_file_cartesc::free_derived_datatype
subroutine free_derived_datatype
free MPI derived datatypes
Definition: scale_file_cartesC.F90:4840
scale_land_grid_cartesc::land_grid_cartesc_fz
real(rp), dimension(:), allocatable, public land_grid_cartesc_fz
face coordinate [m]: z, local=global
Definition: scale_land_grid_cartesC.F90:35
scale_file::file_get_cftunits
subroutine, public file_get_cftunits(date, tunits)
get unit of time
Definition: scale_file.F90:4832
scale_file::file_aggregate
logical, public file_aggregate
Definition: scale_file.F90:182
scale_file_cartesc::file_cartesc_create
subroutine, public file_cartesc_create(basename, title, datatype, fid, date, subsec, haszcoord, append, aggregate, single)
Create/open a netCDF file.
Definition: scale_file_cartesC.F90:780
scale_atmos_grid_cartesc::atmos_grid_cartesc_fz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fz
face coordinate [m]: z, local
Definition: scale_atmos_grid_cartesC.F90:41
scale_atmos_grid_cartesc::atmos_grid_cartesc_name
character(len=7), parameter, public atmos_grid_cartesc_name
Definition: scale_atmos_grid_cartesC.F90:36
scale_file_cartesc::file_cartesc_open
subroutine, public file_cartesc_open(basename, fid, aggregate)
open a netCDF file for read
Definition: scale_file_cartesC.F90:746
scale_file_cartesc::file_cartesc_flush
subroutine, public file_cartesc_flush(fid)
Flush all pending requests to a netCDF file (PnetCDF only)
Definition: scale_file_cartesC.F90:997
scale_file_h::file_fread
integer, parameter, public file_fread
Definition: scale_file_h.F90:32
scale_atmos_grid_cartesc::atmos_grid_cartesc_cyg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cyg
center coordinate [m]: y, global
Definition: scale_atmos_grid_cartesC.F90:76
scale_atmos_grid_cartesc_index::jmax
integer, public jmax
Definition: scale_atmos_grid_cartesC_index.F90:38
scale_file::file_def_variable
subroutine, public file_def_variable(fid, varname, desc, units, standard_name, ndims, dims, dtype, vid, time_int, time_avg, existed)
Definition: scale_file.F90:1571
scale_time::time_nowdate
integer, dimension(6), public time_nowdate
current time [YYYY MM DD HH MM SS]
Definition: scale_time.F90:66
scale_atmos_grid_cartesc_index::js
integer, public js
start point of inner domain: y, local
Definition: scale_atmos_grid_cartesC_index.F90:55
scale_prc_cartesc::prc_num_y
integer, public prc_num_y
y length of 2D processor topology
Definition: scale_prc_cartesC.F90:42
scale_atmos_grid_cartesc::atmos_grid_cartesc_cy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cy
center coordinate [m]: y, local
Definition: scale_atmos_grid_cartesC.F90:56
scale_atmos_grid_cartesc_index::ieb
integer, public ieb
Definition: scale_atmos_grid_cartesC_index.F90:64
scale_file::file_get_aggregate
logical function, public file_get_aggregate(fid)
Definition: scale_file.F90:4844
scale_urban_grid_cartesc_index::uka
integer, public uka
Definition: scale_urban_grid_cartesC_index.F90:36
scale_prof::prof_rapend
subroutine, public prof_rapend(rapname_base, level, disable_barrier)
Save raptime.
Definition: scale_prof.F90:217
scale_const::const_d2r
real(rp), public const_d2r
degree to radian
Definition: scale_const.F90:32
scale_atmos_grid_cartesc::atmos_grid_cartesc_cbfy
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cbfy
center buffer factor (0-1): y
Definition: scale_atmos_grid_cartesC.F90:71
scale_ocean_grid_cartesc_index::oia
integer, public oia
Definition: scale_ocean_grid_cartesC_index.F90:40
scale_land_grid_cartesc
module land / grid / cartesianC
Definition: scale_land_grid_cartesC.F90:11
scale_prc_cartesc::prc_num_x
integer, public prc_num_x
x length of 2D processor topology
Definition: scale_prc_cartesC.F90:41
scale_land_grid_cartesc_index::lke
integer, public lke
Definition: scale_land_grid_cartesC_index.F90:41
scale_file::file_detach_buffer
subroutine, public file_detach_buffer(fid)
Definition: scale_file.F90:4677
scale_atmos_grid_cartesc::atmos_grid_cartesc_cdx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdx
x-length of control volume [m]
Definition: scale_atmos_grid_cartesC.F90:60
scale_file_cartesc::file_cartesc_write_var_1d
subroutine file_cartesc_write_var_1d(fid, vid, var, varname, dim_type)
Write 1D data to file.
Definition: scale_file_cartesC.F90:3500
scale_atmos_grid_cartesc
module atmosphere / grid / cartesC
Definition: scale_atmos_grid_cartesC.F90:12
scale_atmos_grid_cartesc::atmos_grid_cartesc_fdz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdz
z-length of grid(i+1) to grid(i) [m]
Definition: scale_atmos_grid_cartesC.F90:43
scale_atmos_grid_cartesc::atmos_grid_cartesc_cz
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cz
center coordinate [m]: z, local
Definition: scale_atmos_grid_cartesC.F90:40
scale_file_cartesc::file_cartesc_read_auto_2d
subroutine file_cartesc_read_auto_2d(fid, varname, var, step, existed)
Read 2D data from file.
Definition: scale_file_cartesC.F90:1783
scale_file::file_setup
subroutine, public file_setup(myrank)
setup
Definition: scale_file.F90:221
scale_atmos_grid_cartesc::atmos_grid_cartesc_cbfyg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cbfyg
center buffer factor (0-1): y, global
Definition: scale_atmos_grid_cartesC.F90:86
scale_file_cartesc::file_cartesc_setup
subroutine, public file_cartesc_setup
Setup.
Definition: scale_file_cartesC.F90:209
scale_const::const_undef
real(rp), public const_undef
Definition: scale_const.F90:41
scale_file_cartesc::file_cartesc_write_var_3d_t
subroutine file_cartesc_write_var_3d_t(fid, vid, var, varname, dim_type, timeintv, timetarg, timeofs, fill_halo)
Write 3D data with time dimension to file.
Definition: scale_file_cartesC.F90:3888
scale_atmos_grid_cartesc_index::jsb
integer, public jsb
Definition: scale_atmos_grid_cartesC_index.F90:65
scale_file_h::file_file_max
integer, parameter, public file_file_max
Definition: scale_file_h.F90:43
scale_prc_cartesc::prc_has_w
logical, public prc_has_w
Definition: scale_prc_cartesC.F90:47
scale_io::io_fid_conf
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:56
scale_land_grid_cartesc_index::lks
integer, public lks
Definition: scale_land_grid_cartesC_index.F90:40
scale_atmos_grid_cartesc_index::je
integer, public je
end point of inner domain: y, local
Definition: scale_atmos_grid_cartesC_index.F90:56
scale_prc_cartesc::prc_twod
logical, public prc_twod
2D experiment
Definition: scale_prc_cartesC.F90:55
scale_file_cartesc
module file / cartesianC
Definition: scale_file_cartesC.F90:11
scale_file_h::file_real8
integer, parameter, public file_real8
Definition: scale_file_h.F90:25
scale_file::file_create
subroutine, public file_create(basename, title, source, institution, fid, existed, rankid, single, aggregate, time_units, calendar, append)
create file fid is >= 1
Definition: scale_file.F90:267
scale_mapprojection::mapprojection_mappinginfo
type(mappinginfo), public mapprojection_mappinginfo
Definition: scale_mapprojection.F90:104
scale_atmos_grid_cartesc::atmos_grid_cartesc_cx
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cx
center coordinate [m]: x, local
Definition: scale_atmos_grid_cartesC.F90:55
scale_prc::prc_ismaster
logical, public prc_ismaster
master process in local communicator?
Definition: scale_prc.F90:91
scale_atmos_grid_cartesc_index::jsga
integer, public jsga
start point of the full domain: cy, global
Definition: scale_atmos_grid_cartesC_index.F90:83
scale_urban_grid_cartesc_index::uke
integer, public uke
Definition: scale_urban_grid_cartesC_index.F90:38
scale_land_grid_cartesc_index::lka
integer, public lka
Definition: scale_land_grid_cartesC_index.F90:36
scale_urban_grid_cartesc::urban_grid_cartesc_fz
real(rp), dimension(:), allocatable, public urban_grid_cartesc_fz
face coordinate [m]: z, local=global
Definition: scale_urban_grid_cartesC.F90:36
scale_atmos_grid_cartesc::atmos_grid_cartesc_fdxg
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdxg
center coordinate [m]: x, global
Definition: scale_atmos_grid_cartesC.F90:82
scale_file_cartesc::file_cartesc_write_var_2d
subroutine file_cartesc_write_var_2d(fid, vid, var, varname, dim_type, fill_halo)
Write 2D data to file.
Definition: scale_file_cartesC.F90:3586
scale_ocean_grid_cartesc_index::oks
integer, public oks
Definition: scale_ocean_grid_cartesC_index.F90:37