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