SCALE-RM
scale_file_history_cartesC.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
10 !-------------------------------------------------------------------------------
11 #include "scalelib.h"
13  !-----------------------------------------------------------------------------
14  !
15  !++ Used modules
16  !
17  use scale_precision
18  use scale_io
19  use scale_prof
24  use scale_prc, only: &
25  prc_abort
26  !-----------------------------------------------------------------------------
27  implicit none
28  private
29  !-----------------------------------------------------------------------------
30  !
31  !++ Public procedures
32  !
35 
36  !-----------------------------------------------------------------------------
37  !
38  !++ Public parameters & variables
39  !
40  !-----------------------------------------------------------------------------
41  !
42  !++ Private procedures
43  !
44  private :: file_history_cartesc_set_dims
45  private :: file_history_cartesc_set_axes
46  private :: file_history_cartesc_set_axes_attributes
47 
48  !-----------------------------------------------------------------------------
49  !
50  !++ Private parameters & variables
51  !
52  integer, parameter :: nzs = 3
53  character(len=8), parameter :: zs(nzs) = (/ "model ", &
54  "z ", &
55  "pressure" /)
56 
57  integer :: file_history_cartesc_pres_nlayer = 0
58  real(RP), allocatable :: file_history_cartesc_pres_val(:)
59 
60  integer :: im, jm, km
61  integer :: ims, ime
62  integer :: jms, jme
63  integer :: imh, jmh
64  integer :: imsh, jmsh
65 
66  integer :: file_history_cartesc_startdate(6)
67  real(DP) :: file_history_cartesc_startms
68 
69  logical :: file_history_cartesc_boundary = .false.
70 
71  !-----------------------------------------------------------------------------
72 contains
73  !-----------------------------------------------------------------------------
76  use scale_file_h, only: &
78  use scale_file_history, only: &
84  use scale_prc, only: &
87  use scale_prc_cartesc, only: &
90  prc_has_w, &
91  prc_has_s
92  use scale_time, only: &
93  time_nowdate, &
94  time_nowms, &
95  time_nowstep, &
96  time_dtsec, &
98  use scale_calendar, only: &
100  use scale_interp_vert, only: &
102  implicit none
103 
104  integer, parameter :: nlayer_max = 300
105  real(RP) :: FILE_HISTORY_CARTESC_PRES(nlayer_max)
106 
107  namelist / param_file_history_cartesc / &
108  file_history_cartesc_pres_nlayer, &
109  file_history_cartesc_pres, &
110  file_history_cartesc_boundary
111 
112  character(len=H_MID) :: FILE_HISTORY_CARTESC_H_TITLE = 'SCALE-RM FILE_HISTORY_CARTESC OUTPUT'
113  character(len=H_MID) :: FILE_HISTORY_CARTESC_T_SINCE
114 
115  character(len=FILE_HSHORT) :: calendar
116  real(DP) :: start_daysec
117  integer :: ierr
118  integer :: k
119  !---------------------------------------------------------------------------
120 
121  log_newline
122  log_info("FILE_HISTORY_CARTESC_setup",*) 'Setup'
123 
124  file_history_cartesc_pres(:) = 0.0_rp
125 
126  !--- read namelist
127  rewind(io_fid_conf)
128  read(io_fid_conf,nml=param_file_history_cartesc,iostat=ierr)
129  if( ierr < 0 ) then !--- missing
130  log_info("FILE_HISTORY_CARTESC_setup",*) 'Not found namelist. Default used.'
131  elseif( ierr > 0 ) then !--- fatal error
132  log_error("FILE_HISTORY_CARTESC_setup",*) 'Not appropriate names in namelist PARAM_FILE_HISTORY_CARTESC. Check!'
133  call prc_abort
134  endif
135  log_nml(param_file_history_cartesc)
136 
137 
138  ! check pressure coordinate
139  if ( file_history_cartesc_pres_nlayer > 0 ) then
140  if ( file_history_cartesc_pres_nlayer > nlayer_max ) then
141  log_error("FILE_HISTORY_CARTESC_setup",'(a,i3)') 'FILE_HISTORY_CARTESC_PRES_nlayer must be <= ', nlayer_max
142  call prc_abort
143  end if
144  allocate( file_history_cartesc_pres_val(file_history_cartesc_pres_nlayer) )
145 
146  do k = 1, file_history_cartesc_pres_nlayer
147  if ( file_history_cartesc_pres(k) <= 0.0_rp ) then
148  log_error("FILE_HISTORY_CARTESC_setup",'(a,i3,f7.1)') 'Invalid value found in pressure coordinate! (k,value)=', k, file_history_cartesc_pres(k)
149  call prc_abort
150  elseif ( file_history_cartesc_pres(k+1) >= file_history_cartesc_pres(k) ) then
151  log_error("FILE_HISTORY_CARTESC_setup",'(a,i3,2f7.1)') 'The value of pressure coordinate must be descending order! ', &
152  '(k,value[k],value[k+1])=', k, file_history_cartesc_pres(k), file_history_cartesc_pres(k+1)
153  call prc_abort
154  endif
155  file_history_cartesc_pres_val(k) = file_history_cartesc_pres(k) * 100.0_rp ! [hPa->Pa]
156  enddo
157 
158  call interp_vert_alloc_pres( file_history_cartesc_pres_nlayer, ia, ja ) ! [IN]
159  else
160  log_info("FILE_HISTORY_CARTESC_setup",*) 'FILE_HISTORY_CARTESC_PRES_nlayer is not set.'
161  log_info("FILE_HISTORY_CARTESC_setup",*) 'Output with pressure coordinate is disabled'
162  endif
163 
164 
165 
166  file_history_cartesc_startdate(:) = time_nowdate
167  file_history_cartesc_startms = time_nowms
168 
169  start_daysec = time_startdaysec
170  if ( time_nowdate(1) > 0 ) then
171  write(file_history_cartesc_t_since,'(I4.4,5(A1,I2.2))') time_nowdate(1), &
172  '-', time_nowdate(2), &
173  '-', time_nowdate(3), &
174  ' ', time_nowdate(4), &
175  ':', time_nowdate(5), &
176  ':', time_nowdate(6)
177  start_daysec = time_nowms
178  else
179  file_history_cartesc_t_since = ''
180  endif
181 
182  if ( file_history_cartesc_boundary ) then
183  ims = isb
184  ime = ieb
185  jms = jsb
186  jme = jeb
187 
188  imsh = ims
189  jmsh = jms
190 
191  im = imaxb
192  jm = jmaxb
193  imh = im
194  jmh = jm
195  else
196  ims = is
197  ime = ie
198  jms = js
199  jme = je
200 
201  if ( prc_has_w .OR. prc_periodic_x ) then
202  imsh = ims
203  else
204  imsh = ims - 1 ! including i = IS-1
205  endif
206  if ( prc_has_s .OR. prc_periodic_y ) then
207  jmsh = jms
208  else
209  jmsh = jms - 1 ! include j = JS-1
210  endif
211 
212  im = ime - ims + 1
213  jm = jme - jms + 1
214  imh = ime - imsh + 1
215  jmh = jme - jmsh + 1
216  endif
217 
218  ! get calendar name
219  call calendar_get_name( calendar )
220 
221  call file_history_setup( file_history_cartesc_h_title, & ! [IN]
222  h_source, h_institute, & ! [IN]
223  start_daysec, time_dtsec, & ! [IN]
224  time_since = file_history_cartesc_t_since, & ! [IN]
225  calendar = calendar, & ! [IN]
226  default_zcoord = 'model', & ! [IN]
227  myrank = prc_myrank ) ! [IN]
228 
230 
231  call file_history_cartesc_set_dims
232 
233  call file_history_cartesc_set_axes
234 
235  call file_history_cartesc_set_axes_attributes
236 
238  file_history_truncate_2d => file_history_cartesc_truncate_2d
240 
241  return
242  end subroutine file_history_cartesc_setup
243 
244  !-----------------------------------------------------------------------------
246  !-----------------------------------------------------------------------------
247  subroutine file_history_cartesc_set_pres( &
248  PRES, &
249  PRESH, &
250  SFC_PRES )
251  use scale_interp_vert, only: &
253  implicit none
254 
255  real(RP), intent(in) :: PRES (:,:,:) ! pressure at the full level [Pa]
256  real(RP), intent(in) :: PRESH (:,:,:) ! pressure at the half level [Pa]
257  real(RP), intent(in) :: SFC_PRES( :,:) ! surface pressure [Pa]
258  !---------------------------------------------------------------------------
259 
260  if ( file_history_cartesc_pres_nlayer > 0 ) then
261  call interp_vert_setcoef_pres( file_history_cartesc_pres_nlayer, & ! [IN]
262  ka, ks, ke, & ! [IN]
263  ia, isb, ieb, & ! [IN]
264  ja, jsb, jeb, & ! [IN]
265  pres(:,:,:), & ! [IN]
266  presh(:,:,:), & ! [IN]
267  sfc_pres(:,:) , & ! [IN]
268  file_history_cartesc_pres_val(:) ) ! [IN]
269  endif
270 
271  return
272  end subroutine file_history_cartesc_set_pres
273 
274  ! private routines
275 
276  !-----------------------------------------------------------------------------
278  !-----------------------------------------------------------------------------
279  subroutine file_history_cartesc_set_dims
280  use scale_prc, only: &
281  prc_myrank
282  use scale_prc_cartesc, only: &
283  prc_2drank, &
284  prc_has_w, &
285  prc_has_s
286  use scale_file_history, only: &
288  use scale_mapprojection, only: &
290  implicit none
291 
292  character(len=H_SHORT) :: mapping
293 
294  character(len=H_SHORT) :: dims(3,3)
295 
296  integer :: start(3,3), count(3,3)
297  integer :: xs, xc, ys, yc
298  !---------------------------------------------------------------------------
299 
300  ! get start and count for x and y
301  if ( file_history_cartesc_boundary ) then
302  xs = isgb
303  ys = jsgb
304  xc = imaxb
305  yc = jmaxb
306  else
307  ! for the case the shared-file contains no halos
308  xs = prc_2drank(prc_myrank,1) * imax + 1 ! no IHALO
309  xc = imax
310  ys = prc_2drank(prc_myrank,2) * jmax + 1 ! no JHALO
311  yc = jmax
312  end if
313 
314  ! get mapping name
315  call mapprojection_get_attributes( mapping )
316 
317 
318  ! Vertical 1D
319  start(1,1) = 1
320  dims(1,1) = "z"
321  count(1,1) = kmax
322  call file_history_set_dim( "Z", 1, 1, dims(:,:), zs(:), start(:,:), count(:,:) ) ! [IN]
323  dims(1,1) = "zh"
324  count(1,1) = kmax + 1
325  call file_history_set_dim( "ZH", 1, 1, dims(:,:), zs(:), start(:,:), count(:,:) ) ! [IN]
326 
327  dims(1,1) = "oz"
328  count(1,1) = okmax
329  call file_history_set_dim( "OZ", 1, 1, dims(:,:), zs(:), start(:,:), count(:,:) ) ! [IN]
330  dims(1,1) = "ozh"
331  count(1,1) = okmax + 1
332  call file_history_set_dim( "OZH", 1, 1, dims(:,:), zs(:), start(:,:), count(:,:) ) ! [IN]
333 
334  dims(1,1) = "lz"
335  count(1,1) = lkmax
336  call file_history_set_dim( "LZ", 1, 1, dims(:,:), zs(:), start(:,:), count(:,:) ) ! [IN]
337  dims(1,1) = "lzh"
338  count(1,1) = lkmax + 1
339  call file_history_set_dim( "LZH", 1, 1, dims(:,:), zs(:), start(:,:), count(:,:) ) ! [IN]
340 
341  dims(1,1) = "uz"
342  count(1,1) = ukmax
343  call file_history_set_dim( "UZ", 1, 1, dims(:,:), zs(:), start(:,:), count(:,:) ) ! [IN]
344  dims(1,1) = "uzh"
345  count(1,1) = ukmax + 1
346  call file_history_set_dim( "UZH", 1, 1, dims(:,:), zs(:), start(:,:), count(:,:) ) ! [IN]
347 
348  ! X, Y
349  start(1,:) = xs
350  start(2,:) = ys
351  dims(1,:) = 'lon'
352  dims(2,:) = 'lat'
353  count(1,:) = xc
354  count(2,:) = yc
355  call file_history_set_dim( "XY", 2, 1, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, area="cell_area", location="face" ) ! [IN]
356 
357  start(3,:) = 1
358  dims(3,:) = (/ "height ", "z ", "pressure " /)
359  count(3,:) = (/ kmax, kmax, file_history_cartesc_pres_nlayer /)
360  call file_history_set_dim( "ZXY", 3, nzs, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, & ! [IN]
361  area="cell_area", area_x="cell_area_xyz_x", area_y="cell_area_xyz_y", volume="cell_volume", location="face" ) ! [IN]
362  dims(3,:) = (/ "height_xyw", "zh ", "pressure " /)
363  count(3,:) = (/ kmax+1, kmax+1, file_history_cartesc_pres_nlayer /)
364  call file_history_set_dim( "ZHXY", 3, nzs, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, area="cell_area", volume="cell_volume_xyw", location="face" )
365 
366  if ( okmax > 0 ) then
367  dims(3,1) = "oz"
368  count(3,1) = okmax
369  call file_history_set_dim( "OXY", 3, 1, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, area="cell_area", volume="cell_volume_xyo", location="face", grid="ocean" ) ! [IN]
370  dims(3,1) = "ozh"
371  count(3,1) = okmax + 1
372  call file_history_set_dim( "OHXY", 3, 1, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, area="cell_area", location="face", grid="ocean" ) ! [IN]
373  endif
374 
375  if ( lkmax > 0 ) then
376  dims(3,1) = "lz"
377  count(3,1) = lkmax
378  call file_history_set_dim( "LXY", 3, 1, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, area="cell_area", volume="cell_volume_xyl", location="face", grid="land" ) ! [IN]
379  dims(3,1) = "lzh"
380  count(3,1) = lkmax + 1
381  call file_history_set_dim( "LHXY", 3, 1, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, area="cell_area", location="face", grid="land" ) ! [IN]
382  endif
383 
384  if ( ukmax > 0 ) then
385  dims(3,1) = "uz"
386  count(3,1) = ukmax
387  call file_history_set_dim( "UXY", 3, 1, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, area="cell_area", volume="cell_volume_xyu", grid="urban" ) ! [IN]
388  dims(3,1) = "uzh"
389  count(3,1) = ukmax + 1
390  call file_history_set_dim( "UHXY", 3, 1, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, area="cell_area", location="face", grid="urban" ) ! [IN]
391  endif
392 
393  ! XH, Y
394  dims(1,:) = 'lon_uy'
395  dims(2,:) = 'lat_uy'
396  if ( prc_has_w ) then
397  start(1,:) = xs+1
398  count(1,:) = xc
399  else
400  start(1,:) = xs
401  count(1,:) = xc+1
402  endif
403  call file_history_set_dim( "XHY", 2, 1, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, area="cell_area_uy", location="edge1" ) ! [IN]
404 
405  dims(3,:) = (/ "height_uyz", "z ", "pressure " /)
406  count(3,:) = (/ kmax, kmax, file_history_cartesc_pres_nlayer /)
407  call file_history_set_dim( "ZXHY", 3, nzs, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, area="cell_area_uy", volume="cell_volume_uyz", location="edge1" ) ! [IN]
408  dims(3,:) = (/ "height_uyw", "zh ", "pressure " /)
409  count(3,:) = (/ kmax+1, kmax+1, file_history_cartesc_pres_nlayer /)
410  call file_history_set_dim( "ZHXHY", 3, nzs, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, area="cell_area_uy", location="edge1" ) ! [IN]
411 
412  ! X, YH
413  dims(1,:) = 'lon_xv'
414  dims(2,:) = 'lat_xv'
415  start(1,:) = xs
416  count(1,:) = xc
417  if ( prc_has_s ) then
418  start(2,:) = ys+1
419  count(2,:) = yc
420  else
421  start(2,:) = ys
422  count(2,:) = yc+1
423  endif
424  call file_history_set_dim( "XYH", 2, 1, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, area="cell_area_xv", location="edge2" ) ! [IN]
425 
426  dims(3,:) = (/ "height_xvz", "z ", "pressure " /)
427  count(3,:) = (/ kmax, kmax, file_history_cartesc_pres_nlayer /)
428  call file_history_set_dim( "ZXYH", 3, nzs, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, area="cell_area_xv", volume="cell_volume_xvz", location="edge2" ) ! [IN]
429  dims(3,:) = (/ "height_xvw", "zh ", "pressure " /)
430  count(3,:) = (/ kmax+1, kmax+1, file_history_cartesc_pres_nlayer /)
431  call file_history_set_dim( "ZHXYH", 3, nzs, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, area="cell_area_xv", location="edge2" ) ! [IN]
432 
433  ! XH, YH
434  dims(1,:) = 'lon_uv'
435  dims(2,:) = 'lat_uv'
436  if ( prc_has_w ) then
437  start(1,:) = xs+1
438  count(1,:) = xc
439  else
440  start(1,:) = xs
441  count(1,:) = xc+1
442  endif
443  call file_history_set_dim( "XHYH", 2, 1, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, location="face" ) ! [IN]
444 
445  dims(3,:) = (/ "height_uvz", "z ", "pressure " /)
446  count(3,:) = (/ kmax, kmax, file_history_cartesc_pres_nlayer /)
447  call file_history_set_dim( "ZXHYH", 3, nzs, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, & ![IN]
448  area="cell_area_uv", area_x="cell_area_uvz_x", area_y="cell_area_uvz_y", location="node" ) ! [IN]
449  dims(3,:) = (/ "height_uvw", "zh ", "pressure " /)
450  count(3,:) = (/ kmax+1, kmax+1, file_history_cartesc_pres_nlayer /)
451  call file_history_set_dim( "ZHXHYH", 3, nzs, dims(:,:), zs(:), start(:,:), count(:,:), mapping=mapping, location="node" ) ! [IN]
452 
453  return
454  end subroutine file_history_cartesc_set_dims
455 
456  !-----------------------------------------------------------------------------
459  src, &
460  dim_type, zcoord, fill_halo, &
461  dst )
462  implicit none
463 
464  real(RP), intent(in) :: src(:)
465  character(len=*), intent(in) :: dim_type
466  character(len=*), intent(in) :: zcoord
467  logical, intent(in) :: fill_halo ! ignored
468 
469  real(DP), intent(out) :: dst(:)
470 
471  integer :: ksize
472  integer :: kstart
473  integer :: k
474  !---------------------------------------------------------------------------
475 
476  ! select dimension
477  select case ( dim_type )
478  case ('Z')
479  ksize = kmax
480  kstart = ks
481  case ('ZH')
482  ksize = kmax+1
483  kstart = ks-1
484  case ('OZ')
485  ksize = okmax
486  kstart = oks
487  case ('OZH')
488  ksize = okmax+1
489  kstart = oks-1
490  case ('LZ')
491  ksize = lkmax
492  kstart = lks
493  case ('LZH')
494  ksize = lkmax+1
495  kstart = lks-1
496  case ('UZ')
497  ksize = ukmax
498  kstart = uks
499  case ('UZH')
500  ksize = ukmax+1
501  kstart = uks-1
502  case default
503  log_error("FILE_HISTORY_CARTESC_truncate_1D",*) 'dim_type is invalid: ', trim(dim_type)
504  call prc_abort
505  end select
506 
507  do k = 1, ksize
508  dst(k) = src(kstart+k-1)
509  enddo
510 
511  return
512  end subroutine file_history_cartesc_truncate_1d
513 
514  !-----------------------------------------------------------------------------
516  subroutine file_history_cartesc_truncate_2d( &
517  src, &
518  dim_type, zcoord, fill_halo, &
519  dst )
520  use scale_file_h, only: &
521  rmiss => file_rmiss
522  implicit none
523 
524  real(RP), intent(in) :: src(:,:)
525  character(len=*), intent(in) :: dim_type
526  character(len=*), intent(in) :: zcoord ! ignored
527  logical, intent(in) :: fill_halo
528 
529  real(DP), intent(out) :: dst(:)
530 
531  integer :: isize, jsize
532  integer :: istart, jstart
533  integer :: i, j
534  !---------------------------------------------------------------------------
535 
536  ! select dimension
537  select case( dim_type )
538  case ( 'XY', 'XYH' )
539  isize = im
540  istart = ims
541  case ( 'XHY', 'XHYH' )
542  isize = imh
543  istart = imsh
544  case default
545  log_error("FILE_HISTORY_CARTESC_truncate_2D",*) 'dim_type is invalid: ', trim(dim_type)
546  call prc_abort
547  end select
548 
549  select case ( dim_type )
550  case ( 'XY', 'XHY' )
551  jsize = jm
552  jstart = jms
553  case ( 'XYH', 'XHYH' )
554  jsize = jmh
555  jstart = jmsh
556  case default
557  log_error("FILE_HISTORY_CARTESC_truncate_2D",*) 'dim_type is invalid: ', trim(dim_type)
558  call prc_abort
559  end select
560 
561  !$omp parallel do
562  do j = 1, jsize
563  do i = 1, isize
564  dst((j-1)*isize+i) = src(istart+i-1,jstart+j-1)
565  enddo
566  enddo
567 
568  if ( fill_halo ) then
569  ! W halo
570  do j = 1, jsize
571  do i = 1, is-istart
572  dst((j-1)*isize+i) = rmiss
573  enddo
574  enddo
575  ! E halo
576  do j = 1, jsize
577  do i = ie-istart+2, ime-istart+1
578  dst((j-1)*isize+i) = rmiss
579  enddo
580  enddo
581  ! S halo
582  do j = 1, js-jstart
583  do i = 1, isize
584  dst((j-1)*isize+i) = rmiss
585  enddo
586  enddo
587  ! N halo
588  do j = je-jstart+2, jme-jstart+1
589  do i = 1, isize
590  dst((j-1)*isize+i) = rmiss
591  enddo
592  enddo
593 
594  end if
595 
596  return
597  end subroutine file_history_cartesc_truncate_2d
598 
599  !-----------------------------------------------------------------------------
602  src, &
603  dim_type, zcoord, fill_halo, &
604  dst )
605  use scale_file_h, only: &
606  rmiss => file_rmiss
607  use scale_atmos_grid_cartesc, only: &
610  use scale_atmos_grid_cartesc_real, only: &
613  use scale_interp_vert, only: &
619  implicit none
620 
621  real(RP), intent(in) :: src(:,:,:)
622  character(len=*), intent(in) :: dim_type
623  character(len=*), intent(in) :: zcoord
624  logical, intent(in) :: fill_halo
625  real(DP), intent(out) :: dst(:)
626 
627  real(RP) :: src_Z(ka,ia,ja)
628  real(RP) :: src_P(file_history_cartesc_pres_nlayer,ia,ja)
629 
630  integer :: isize, jsize, ksize
631  integer :: istart, jstart, kstart
632  integer :: i, j, k
633  !---------------------------------------------------------------------------
634 
635  ! select dimension
636  if ( index( dim_type, 'XH' ) == 0 ) then
637  isize = im
638  istart = ims
639  else
640  isize = imh
641  istart = imsh
642  end if
643 
644  if ( index( dim_type, 'YH' ) == 0 ) then
645  jsize = jm
646  jstart = jms
647  else
648  jsize = jmh
649  jstart = jmsh
650  end if
651 
652  select case( dim_type(1:1) )
653  case ( 'Z' )
654  ksize = kmax
655  kstart = ks
656  case('O')
657  ksize = okmax
658  kstart = oks
659  case('L')
660  ksize = lkmax
661  kstart = lks
662  case('U')
663  ksize = ukmax
664  kstart = uks
665  case default
666  log_error("FILE_HISTORY_CARTESC_truncate_3D",*) 'dim_type is invalid: ', trim(dim_type)
667  call prc_abort
668  end select
669  if ( dim_type(2:2) == 'H' ) then
670  ksize = ksize + 1
671  kstart = kstart - 1
672  end if
673 
674 
675  if ( ksize == kmax .and. zcoord == "z" .and. interp_available ) then ! z*->z interpolation (full level)
676 
677  call prof_rapstart('FILE_O_interp', 2)
678  call interp_vert_xi2z( ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
679  atmos_grid_cartesc_cz(:), & ! [IN]
680  atmos_grid_cartesc_real_cz(:,:,:), & ! [IN]
681  src(:,:,:), & ! [IN]
682  src_z(:,:,:) ) ! [OUT]
683  call prof_rapend ('FILE_O_interp', 2)
684 
685  !$omp parallel do
686  do k = 1, ksize
687  do j = 1, jsize
688  do i = 1, isize
689  dst((k-1)*jsize*isize+(j-1)*isize+i) = src_z(kstart+k-1,istart+i-1,jstart+j-1)
690  enddo
691  enddo
692  enddo
693 
694  else if( ksize == kmax+1 .and. zcoord == "z" .and. interp_available ) then ! z*->z interpolation (half level)
695 
696 
697  call prof_rapstart('FILE_O_interp', 2)
698  call interp_vert_xih2zh( ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
699  atmos_grid_cartesc_fz(:), & ! [IN]
700  atmos_grid_cartesc_real_fz(:,:,:), & ! [IN]
701  src(:,:,:), & ! [IN]
702  src_z(:,:,:) ) ! [OUT]
703  call prof_rapend ('FILE_O_interp', 2)
704 
705  !$omp parallel do
706  do k = 1, ksize
707  do j = 1, jsize
708  do i = 1, isize
709  dst((k-1)*jsize*isize+(j-1)*isize+i) = src_z(kstart+k-1,istart+i-1,jstart+j-1)
710  enddo
711  enddo
712  enddo
713 
714  elseif( ksize == kmax .and. zcoord == "pressure" ) then ! z*->p interpolation (full level)
715  ksize = file_history_cartesc_pres_nlayer
716  if ( ksize == 0 ) then
717  log_error("FILE_HISTORY_CARTESC_truncate_3D",*) 'FILE_HISTORY_CARTESC_PRES_nlayer must be set to output variable with the pressure coordinate'
718  call prc_abort
719  end if
720 
721  call prof_rapstart('FILE_O_interp', 2)
722  call interp_vert_xi2p( file_history_cartesc_pres_nlayer, & ! [IN]
723  ka, & ! [IN]
724  ia, isb, ieb, & ! [IN]
725  ja, jsb, jeb, & ! [IN]
726  src(:,:,:), & ! [IN]
727  src_p(:,:,:) ) ! [OUT]
728  call prof_rapend ('FILE_O_interp', 2)
729 
730  !$omp parallel do
731  do k = 1, ksize
732  do j = 1, jsize
733  do i = 1, isize
734  dst((k-1)*jsize*isize+(j-1)*isize+i) = src_p(k,istart+i-1,jstart+j-1)
735  enddo
736  enddo
737  enddo
738 
739  elseif( ksize == kmax+1 .and. zcoord == "pressure" ) then ! z*->p interpolation (half level)
740  ksize = file_history_cartesc_pres_nlayer
741  if ( ksize == 0 ) then
742  log_error("FILE_HISTORY_CARTESC_truncate_3D",*) 'FILE_HISTORY_CARTESC_PRES_nlayer must be set to output variable with the pressure coordinate'
743  call prc_abort
744  end if
745 
746  call prof_rapstart('FILE_O_interp', 2)
747  call interp_vert_xih2p( file_history_cartesc_pres_nlayer, & ! [IN]
748  ka, & ! [IN]
749  ia, isb, ieb, & ! [IN]
750  ja, jsb, jeb, & ! [IN]
751  src(:,:,:), & ! [IN]
752  src_p(:,:,:) ) ! [OUT]
753  call prof_rapend ('FILE_O_interp', 2)
754 
755  do k = 1, ksize
756  do j = 1, jsize
757  do i = 1, isize
758  dst((k-1)*jsize*isize+(j-1)*isize+i) = src_p(k,istart+i-1,jstart+j-1)
759  enddo
760  enddo
761  enddo
762 
763  else ! no interpolation
764 
765  do k = 1, ksize
766  do j = 1, jsize
767  do i = 1, isize
768  dst((k-1)*jsize*isize+(j-1)*isize+i) = src(kstart+k-1,istart+i-1,jstart+j-1)
769  enddo
770  enddo
771  enddo
772 
773  endif
774 
775  if ( fill_halo ) then
776  ! W halo
777  do k = 1, ksize
778  do j = 1, jsize
779  do i = 1, is-istart
780  dst((k-1)*jsize*isize+(j-1)*isize+i) = rmiss
781  enddo
782  enddo
783  enddo
784  ! E halo
785  do k = 1, ksize
786  do j = 1, jsize
787  do i = ie-istart+2, ime-istart+1
788  dst((k-1)*jsize*isize+(j-1)*isize+i) = rmiss
789  enddo
790  enddo
791  enddo
792  ! S halo
793  do k = 1, ksize
794  do j = 1, js-jstart
795  do i = 1, isize
796  dst((k-1)*jsize*isize+(j-1)*isize+i) = rmiss
797  enddo
798  enddo
799  enddo
800  ! N halo
801  do k = 1, ksize
802  do j = je-jstart+2, jme-jstart+1
803  do i = 1, isize
804  dst((k-1)*jsize*isize+(j-1)*isize+i) = rmiss
805  enddo
806  enddo
807  enddo
808  endif
809 
810  return
811  end subroutine file_history_cartesc_truncate_3d
812 
813  !-----------------------------------------------------------------------------
815  ! only register the axis and coordinate variables into internal buffers
816  ! The actual write happens later when calling FILE_HISTORY_CARTESC_write
817  subroutine file_history_cartesc_set_axes
818  use scale_file_history, only: &
821  file_history_set_associatedcoordinate
822  use scale_const, only: &
823  undef => const_undef, &
824  d2r => const_d2r
825  use scale_prc, only: &
826  prc_myrank
827  use scale_prc_cartesc, only: &
828  prc_2drank, &
829  prc_num_x, &
830  prc_num_y, &
831  prc_periodic_x, &
832  prc_periodic_y, &
833  prc_has_w, &
834  prc_has_s
835  use scale_atmos_grid_cartesc, only: &
866  use scale_ocean_grid_cartesc, only: &
870  use scale_land_grid_cartesc, only: &
874  use scale_urban_grid_cartesc, only: &
878  use scale_atmos_grid_cartesc_real, only: &
890  areauy => atmos_grid_cartesc_real_areauy, &
891  areaxv => atmos_grid_cartesc_real_areaxv, &
892  areazuy_x => atmos_grid_cartesc_real_areazuy_x, &
893  areazxv_y => atmos_grid_cartesc_real_areazxv_y, &
894  areawuy_x => atmos_grid_cartesc_real_areawuy_x, &
895  areawxv_y => atmos_grid_cartesc_real_areawxv_y, &
896  areazxy_x => atmos_grid_cartesc_real_areazxy_x, &
897  areazuv_y => atmos_grid_cartesc_real_areazuv_y, &
898  areazuv_x => atmos_grid_cartesc_real_areazuv_x, &
899  areazxy_y => atmos_grid_cartesc_real_areazxy_y, &
901  volwxy => atmos_grid_cartesc_real_volwxy, &
902  volzuy => atmos_grid_cartesc_real_volzuy, &
904  use scale_ocean_grid_cartesc_real, only: &
906  use scale_land_grid_cartesc_real, only: &
908  use scale_urban_grid_cartesc_real, only: &
910  use scale_topography, only: &
911  topo_zsfc
912  use scale_landuse, only: &
914  implicit none
915 
916  real(RP) :: AXIS (imh,jmh,0:kmax)
917  real(RP) :: AXISO(im, jm, okmax)
918  real(RP) :: AXISL(im, jm, lkmax)
919  real(RP) :: AXISU(im, jm, ukmax)
920  character(len=2) :: AXIS_name(3)
921 
922  integer :: rankidx(2)
923  integer :: start(3,4)
924  integer :: startX, startY, startZ
925  integer :: startXH, startYH
926  integer :: XAG, YAG
927  integer :: XAGH, YAGH
928 
929  real(RP) :: z_bnds(2,ka), zh_bnds(2,0:ka)
930  real(RP) :: oz_bnds(2,oka), ozh_bnds(2,0:oka)
931  real(RP) :: lz_bnds(2,lka), lzh_bnds(2,0:lka)
932  real(RP) :: uz_bnds(2,uka), uzh_bnds(2,0:uka)
933  real(RP) :: x_bnds(2,ia), xh_bnds(2,0:ia)
934  real(RP) :: y_bnds(2,ja), yh_bnds(2,0:ja)
935 
936  real(RP) :: FDXG(0:iag), FDYG(0:jag)
937  real(RP) :: FDX(0:ia), FDY(0:ja)
938 
939  integer :: k, i, j
940  !---------------------------------------------------------------------------
941 
942  rankidx(1) = prc_2drank(prc_myrank,1)
943  rankidx(2) = prc_2drank(prc_myrank,2)
944 
945  ! For parallel I/O, some variables are written by a subset of processes.
946  ! 1. Only PRC_myrank 0 writes all z axes
947  ! 2. Only south-most processes (rankidx(2) == 0) write x axes
948  ! rankidx(1) == 0 writes west HALO
949  ! rankidx(1) == PRC_NUM_X-1 writes east HALO
950  ! others writes without HALO
951  ! 3. Only west-most processes (rankidx(1) == 0) write y axes
952  ! rankidx(1) == 0 writes south HALO
953  ! rankidx(1) == PRC_NUM_Y-1 writes north HALO
954  ! others writes without HALO
955 
956  if ( file_history_aggregate ) then
957 
958  startz = 1
959 
960  if ( file_history_cartesc_boundary ) then
961  startx = isgb ! global subarray starting index
962  starty = jsgb ! global subarray starting index
963  startxh = startx
964  startyh = starty
965  xag = iagb
966  yag = jagb
967  xagh = xag
968  yagh = yag
969  else
970  startx = prc_2drank(prc_myrank,1) * imax + 1
971  starty = prc_2drank(prc_myrank,2) * jmax + 1
972  startxh = startx
973  startyh = starty
974  xag = imaxg
975  yag = jmaxg
976  xagh = xag
977  yagh = yag
978 
979  if ( .NOT. prc_periodic_x ) then
980  xagh = xagh + 1
981  if( prc_has_w ) startxh = startxh + 1
982  endif
983 
984  if ( .NOT. prc_periodic_y ) then
985  yagh = yagh + 1
986  if( prc_has_s ) startyh = startyh + 1
987  endif
988  endif
989 
990  ! for shared-file parallel I/O, only a part of rank writes variables
991  if ( prc_myrank > 0 ) then ! only rank 0 writes Z axes
992  startz = -1
993  endif
994  if ( rankidx(2) > 0 ) then ! only south-most processes write
995  startx = -1
996  startxh = -1
997  endif
998  if ( rankidx(1) > 0 ) then ! only west-most processes write
999  starty = -1
1000  startyh = -1
1001  endif
1002  else
1003  startz = 1
1004  startx = 1
1005  starty = 1
1006  startxh = startx
1007  startyh = starty
1008  xag = im
1009  yag = jm
1010  xagh = imh
1011  yagh = jmh
1012  endif
1013 
1014  ! bounds
1015  do k = ks, ke
1016  z_bnds(1,k) = atmos_grid_cartesc_fz(k-1)
1017  z_bnds(2,k) = atmos_grid_cartesc_fz(k )
1018  end do
1019  do k = ks-1, ke
1020  zh_bnds(1,k) = atmos_grid_cartesc_cz(k )
1021  zh_bnds(2,k) = atmos_grid_cartesc_cz(k+1)
1022  end do
1023 
1024  if ( oka > 0 ) then
1025  do k = oks, oke
1026  oz_bnds(1,k) = ocean_grid_cartesc_fz(k-1)
1027  oz_bnds(2,k) = ocean_grid_cartesc_fz(k )
1028  end do
1029  ozh_bnds(1,oks-1) = ocean_grid_cartesc_fz(oks-1)
1030  do k = oks-1, oke-1
1031  ozh_bnds(2,k ) = ocean_grid_cartesc_cz(k+1)
1032  ozh_bnds(1,k+1) = ocean_grid_cartesc_cz(k+1)
1033  end do
1034  ozh_bnds(2,oke) = ocean_grid_cartesc_fz(oke)
1035  end if
1036 
1037  if ( lka > 0 ) then
1038  do k = lks, lke
1039  lz_bnds(1,k) = land_grid_cartesc_fz(k-1)
1040  lz_bnds(2,k) = land_grid_cartesc_fz(k )
1041  end do
1042  lzh_bnds(1,lks-1) = land_grid_cartesc_fz(lks-1)
1043  do k = lks-1, lke-1
1044  lzh_bnds(2,k ) = land_grid_cartesc_cz(k+1)
1045  lzh_bnds(1,k+1) = land_grid_cartesc_cz(k+1)
1046  end do
1047  lzh_bnds(2,lke) = land_grid_cartesc_fz(lke)
1048  end if
1049 
1050  if ( uka > 0 ) then
1051  do k = uks, uke
1052  uz_bnds(1,k) = urban_grid_cartesc_fz(k-1)
1053  uz_bnds(2,k) = urban_grid_cartesc_fz(k )
1054  end do
1055  uzh_bnds(1,uks-1) = urban_grid_cartesc_fz(uks-1)
1056  do k = uks-1, uke-1
1057  uzh_bnds(2,k ) = urban_grid_cartesc_cz(k+1)
1058  uzh_bnds(1,k+1) = urban_grid_cartesc_cz(k+1)
1059  end do
1060  uzh_bnds(2,uke) = urban_grid_cartesc_fz(uke)
1061  end if
1062 
1063  do i = ims, ime
1064  x_bnds(1,i) = atmos_grid_cartesc_fx(i-1)
1065  x_bnds(2,i) = atmos_grid_cartesc_fx(i )
1066  end do
1067  if ( imsh == 0 ) then
1068  xh_bnds(1,0) = atmos_grid_cartesc_fx(0)
1069  else
1070  xh_bnds(1,imsh) = atmos_grid_cartesc_cx(imsh)
1071  end if
1072  do i = imsh, ime-1
1073  xh_bnds(2,i ) = atmos_grid_cartesc_cx(i+1)
1074  xh_bnds(1,i+1) = atmos_grid_cartesc_cx(i+1)
1075  end do
1076  if ( ime == ia ) then
1077  xh_bnds(2,ime) = atmos_grid_cartesc_fx(ia)
1078  else
1079  xh_bnds(2,ime) = atmos_grid_cartesc_cx(ime+1)
1080  end if
1081 
1082  do j = jms, jme
1083  y_bnds(1,j) = atmos_grid_cartesc_fy(j-1)
1084  y_bnds(2,j) = atmos_grid_cartesc_fy(j )
1085  end do
1086  if ( jmsh == 0 ) then
1087  yh_bnds(1,jmsh) = atmos_grid_cartesc_fy(jmsh)
1088  else
1089  yh_bnds(1,jmsh) = atmos_grid_cartesc_cy(jmsh)
1090  end if
1091  do j = jmsh, jme-1
1092  yh_bnds(2,j ) = atmos_grid_cartesc_cy(j+1)
1093  yh_bnds(1,j+1) = atmos_grid_cartesc_cy(j+1)
1094  end do
1095  if ( jme == ja ) then
1096  yh_bnds(2,jme) = atmos_grid_cartesc_fy(jme)
1097  else
1098  yh_bnds(2,jme) = atmos_grid_cartesc_cy(jme+1)
1099  end if
1100 
1101 
1102  fdxg(1:iag-1) = atmos_grid_cartesc_fdxg(:)
1103  fdxg(0 ) = undef
1104  fdxg(iag) = undef
1105  fdyg(1:jag-1) = atmos_grid_cartesc_fdyg(:)
1106  fdyg(0 ) = undef
1107  fdyg(jag) = undef
1108 
1109  fdx(1:ia-1) = atmos_grid_cartesc_fdx(:)
1110  fdx(0 ) = fdxg(is_ing-ihalo-1)
1111  fdx(ia) = fdxg(ie_ing+ihalo )
1112  fdy(1:ja-1) = atmos_grid_cartesc_fdy(:)
1113  fdy(0 ) = fdyg(js_ing-jhalo-1)
1114  fdy(ja) = fdyg(je_ing+jhalo )
1115 
1116 
1117  ! for the shared-file I/O method, the axes are global (gsize)
1118  ! for one-file-per-process I/O method, the axes size is equal to the local buffer size
1119 
1120  call file_history_set_axis( 'z', 'Z', 'm', 'z', atmos_grid_cartesc_cz(ks :ke), &
1121  bounds=z_bnds(:,ks :ke), gsize=kmax , start=startz )
1122  call file_history_set_axis( 'zh', 'Z (half level)', 'm', 'zh', atmos_grid_cartesc_fz(ks-1:ke), &
1123  bounds=zh_bnds(:,ks-1:ke), gsize=kmax+1 , start=startz )
1124 
1125  if ( file_history_cartesc_pres_nlayer > 0 ) then
1126  call file_history_set_axis( 'pressure', 'Pressure', 'hPa', 'pressure', file_history_cartesc_pres_val(:)/100.0_rp, &
1127  gsize=file_history_cartesc_pres_nlayer, start=startz, down=.true. )
1128  endif
1129 
1130  if ( oka > 0 ) then
1131  call file_history_set_axis( 'oz', 'OZ', 'm', 'oz', ocean_grid_cartesc_cz(oks :oke), &
1132  bounds=oz_bnds(:,oks :oke), gsize=okmax , start=startz, down=.true. )
1133  call file_history_set_axis( 'ozh', 'OZ (half level)', 'm', 'ozh', ocean_grid_cartesc_fz(oks-1:oke), &
1134  bounds=ozh_bnds(:,oks-1:oke), gsize=okmax+1, start=startz, down=.true. )
1135  endif
1136 
1137  if ( lka > 0 ) then
1138  call file_history_set_axis( 'lz', 'LZ', 'm', 'lz', land_grid_cartesc_cz(lks :lke), &
1139  bounds=lz_bnds(:,lks :lke), gsize=lkmax , start=startz, down=.true. )
1140  call file_history_set_axis( 'lzh', 'LZ (half level)', 'm', 'lzh', land_grid_cartesc_fz(lks-1:lke), &
1141  bounds=lzh_bnds(:,lks-1:lke), gsize=lkmax+1, start=startz, down=.true. )
1142  endif
1143 
1144  if ( uka > 0 ) then
1145  call file_history_set_axis( 'uz', 'UZ', 'm', 'uz', urban_grid_cartesc_cz(uks :uke), &
1146  bounds=uz_bnds(:,uks :uke), gsize=ukmax , start=startz, down=.true. )
1147  call file_history_set_axis( 'uzh', 'UZ (half level)', 'm', 'uzh', urban_grid_cartesc_fz(uks-1:uke), &
1148  bounds=uzh_bnds(:,uks-1:uke), gsize=ukmax+1, start=startz, down=.true. )
1149  endif
1150 
1151  call file_history_set_axis( 'x', 'X', 'm', 'x', atmos_grid_cartesc_cx(ims :ime), &
1152  bounds=x_bnds(:,ims :ime), gsize=xag , start=startx )
1153  call file_history_set_axis( 'xh', 'X (half level)', 'm', 'xh', atmos_grid_cartesc_fx(imsh:ime), &
1154  bounds=xh_bnds(:,imsh:ime), gsize=xagh, start=startxh )
1155 
1156  call file_history_set_axis( 'y', 'Y', 'm', 'y', atmos_grid_cartesc_cy(jms :jme), &
1157  bounds=y_bnds(:,jms :jme), gsize=yag , start=starty )
1158  call file_history_set_axis( 'yh', 'Y (half level)', 'm', 'yh', atmos_grid_cartesc_fy(jmsh:jme), &
1159  bounds=yh_bnds(:,jmsh:jme), gsize=yagh, start=startyh )
1160 
1161  ! axes below always include halos when written to file regardless of PRC_PERIODIC_X/PRC_PERIODIC_Y
1162  call file_history_set_axis( 'CZ', 'Atmos Grid Center Position Z', 'm', 'CZ', atmos_grid_cartesc_cz, gsize=ka, start=startz )
1163  call file_history_set_axis( 'FZ', 'Atmos Grid Face Position Z', 'm', 'FZ', atmos_grid_cartesc_fz, gsize=ka+1, start=startz )
1164  call file_history_set_axis( 'CDZ', 'Grid Cell length Z', 'm', 'CZ', atmos_grid_cartesc_cdz, gsize=ka, start=startz )
1165  call file_history_set_axis( 'FDZ', 'Grid distance Z', 'm', 'FDZ', atmos_grid_cartesc_fdz, gsize=ka-1, start=startz )
1166  call file_history_set_axis( 'CBFZ', 'Boundary factor Center Z', '1', 'CZ', atmos_grid_cartesc_cbfz, gsize=ka, start=startz )
1167  call file_history_set_axis( 'FBFZ', 'Boundary factor Face Z', '1', 'FZ', atmos_grid_cartesc_fbfz, gsize=ka+1, start=startz )
1168 
1169  if ( okmax > 0 ) then
1170  call file_history_set_axis( 'OCZ', 'Ocean Grid Center Position Z', 'm', 'OCZ', ocean_grid_cartesc_cz, gsize=okmax, start=startz, down=.true. )
1171  call file_history_set_axis( 'OFZ', 'Ocean Grid Face Position Z', 'm', 'OFZ', ocean_grid_cartesc_fz, gsize=okmax+1, start=startz, down=.true. )
1172  call file_history_set_axis( 'OCDZ', 'Ocean Grid Cell length Z', 'm', 'OCZ', ocean_grid_cartesc_cdz, gsize=okmax, start=startz )
1173  endif
1174 
1175  if ( lkmax > 0 ) then
1176  call file_history_set_axis( 'LCZ', 'Land Grid Center Position Z', 'm', 'LCZ', land_grid_cartesc_cz, gsize=lkmax, start=startz, down=.true. )
1177  call file_history_set_axis( 'LFZ', 'Land Grid Face Position Z', 'm', 'LFZ', land_grid_cartesc_fz, gsize=lkmax+1, start=startz, down=.true. )
1178  call file_history_set_axis( 'LCDZ', 'Land Grid Cell length Z', 'm', 'LCZ', land_grid_cartesc_cdz, gsize=lkmax, start=startz )
1179  endif
1180 
1181  if ( ukmax > 0 ) then
1182  call file_history_set_axis( 'UCZ', 'Urban Grid Center Position Z', 'm', 'UCZ', urban_grid_cartesc_cz, gsize=ukmax, start=startz, down=.true. )
1183  call file_history_set_axis( 'UFZ', 'Urban Grid Face Position Z', 'm', 'UFZ', urban_grid_cartesc_fz, gsize=ukmax+1, start=startz, down=.true. )
1184  call file_history_set_axis( 'UCDZ', 'Urban Grid Cell length Z', 'm', 'UCZ', urban_grid_cartesc_cdz, gsize=ukmax, start=startz )
1185  endif
1186 
1187  if ( file_history_aggregate ) then
1188  call file_history_set_axis( 'CX', 'Atmos Grid Center Position X', 'm', 'CX', atmos_grid_cartesc_cxg, gsize=iag, start=startz )
1189  call file_history_set_axis( 'CY', 'Atmos Grid Center Position Y', 'm', 'CY', atmos_grid_cartesc_cyg, gsize=jag, start=startz )
1190  call file_history_set_axis( 'FX', 'Atmos Grid Face Position X', 'm', 'FX', atmos_grid_cartesc_fxg, gsize=iag+1, start=startz )
1191  call file_history_set_axis( 'FY', 'Atmos Grid Face Position Y', 'm', 'FY', atmos_grid_cartesc_fyg, gsize=jag+1, start=startz )
1192  call file_history_set_axis( 'CDX', 'Grid Cell length X', 'm', 'CX', atmos_grid_cartesc_cdxg, gsize=iag, start=startz )
1193  call file_history_set_axis( 'CDY', 'Grid Cell length Y', 'm', 'CY', atmos_grid_cartesc_cdyg, gsize=jag, start=startz )
1194  call file_history_set_axis( 'FDX', 'Grid distance X', 'm', 'FX', fdxg, gsize=iag+1, start=startz )
1195  call file_history_set_axis( 'FDY', 'Grid distance Y', 'm', 'FY', fdyg, gsize=jag+1, start=startz )
1196  call file_history_set_axis( 'CBFX', 'Boundary factor Center X', '1', 'CX', atmos_grid_cartesc_cbfxg, gsize=iag, start=startz )
1197  call file_history_set_axis( 'CBFY', 'Boundary factor Center Y', '1', 'CY', atmos_grid_cartesc_cbfyg, gsize=jag, start=startz )
1198  call file_history_set_axis( 'FBFX', 'Boundary factor Face X', '1', 'FX', atmos_grid_cartesc_fbfxg, gsize=iag+1, start=startz )
1199  call file_history_set_axis( 'FBFY', 'Boundary factor Face Y', '1', 'FY', atmos_grid_cartesc_fbfyg, gsize=jag+1, start=startz )
1200  else
1201  call file_history_set_axis( 'CX', 'Atmos Grid Center Position X', 'm', 'CX', atmos_grid_cartesc_cx )
1202  call file_history_set_axis( 'CY', 'Atmos Grid Center Position Y', 'm', 'CY', atmos_grid_cartesc_cy )
1203  call file_history_set_axis( 'FX', 'Atmos Grid Face Position X', 'm', 'FX', atmos_grid_cartesc_fx )
1204  call file_history_set_axis( 'FY', 'Atmos Grid Face Position Y', 'm', 'FY', atmos_grid_cartesc_fy )
1205  call file_history_set_axis( 'CDX', 'Grid Cell length X', 'm', 'CX', atmos_grid_cartesc_cdx )
1206  call file_history_set_axis( 'CDY', 'Grid Cell length Y', 'm', 'CY', atmos_grid_cartesc_cdy )
1207  call file_history_set_axis( 'FDX', 'Grid distance X', 'm', 'FX', fdx )
1208  call file_history_set_axis( 'FDY', 'Grid distance Y', 'm', 'FY', fdy )
1209  call file_history_set_axis( 'CBFX', 'Boundary factor Center X', '1', 'CX', atmos_grid_cartesc_cbfx )
1210  call file_history_set_axis( 'CBFY', 'Boundary factor Center Y', '1', 'CY', atmos_grid_cartesc_cbfy )
1211  call file_history_set_axis( 'FBFX', 'Boundary factor Face X', '1', 'FX', atmos_grid_cartesc_fbfx )
1212  call file_history_set_axis( 'FBFY', 'Boundary factor Face Y', '1', 'FY', atmos_grid_cartesc_fbfy )
1213  endif
1214 
1215  call file_history_set_axis('CXG', 'Grid Center Position X (global)', 'm', 'CXG', atmos_grid_cartesc_cxg, gsize=iag, start=startz )
1216  call file_history_set_axis('CYG', 'Grid Center Position Y (global)', 'm', 'CYG', atmos_grid_cartesc_cyg, gsize=jag, start=startz )
1217  call file_history_set_axis('FXG', 'Grid Face Position X (global)', 'm', 'FXG', atmos_grid_cartesc_fxg, gsize=iag+1, start=startz )
1218  call file_history_set_axis('FYG', 'Grid Face Position Y (global)', 'm', 'FYG', atmos_grid_cartesc_fyg, gsize=jag+1, start=startz )
1219  call file_history_set_axis('CDXG', 'Grid Cell length X (global)', 'm', 'CXG', atmos_grid_cartesc_cdxg, gsize=iag, start=startz )
1220  call file_history_set_axis('CDYG', 'Grid Cell length Y (global)', 'm', 'CYG', atmos_grid_cartesc_cdyg, gsize=jag, start=startz )
1221  call file_history_set_axis('FDXG', 'Grid distance X (global)', 'm', 'FDXG', fdxg, gsize=iag+1, start=startz )
1222  call file_history_set_axis('FDYG', 'Grid distance Y (global)', 'm', 'FDYG', fdyg, gsize=jag+1, start=startz )
1223  call file_history_set_axis('CBFXG', 'Boundary factor Center X (global)', '1', 'CXG', atmos_grid_cartesc_cbfxg, gsize=iag, start=startz )
1224  call file_history_set_axis('CBFYG', 'Boundary factor Center Y (global)', '1', 'CYG', atmos_grid_cartesc_cbfyg, gsize=jag, start=startz )
1225  call file_history_set_axis('FBFXG', 'Boundary factor Face X (global)', '1', 'FXG', atmos_grid_cartesc_fbfxg, gsize=iag+1, start=startz )
1226  call file_history_set_axis('FBFYG', 'Boundary factor Face Y (global)', '1', 'FYG', atmos_grid_cartesc_fbfyg, gsize=jag+1, start=startz )
1227 
1228 
1229 
1230  ! associate coordinates
1231  if ( file_history_aggregate ) then
1232  if ( file_history_cartesc_boundary ) then
1233  start(1,:) = isgb ! global subarray starting index
1234  start(2,:) = jsgb ! global subarray starting index
1235  else
1236  start(1,:) = prc_2drank(prc_myrank,1) * imax + 1 ! no IHALO
1237  start(2,:) = prc_2drank(prc_myrank,2) * jmax + 1 ! no JHALO
1238  if ( (.NOT. prc_periodic_x) .AND. prc_has_w ) then
1239  start(1,2) = start(1,2) + 1
1240  start(1,4) = start(1,4) + 1
1241  endif
1242  if ( (.NOT. prc_periodic_y) .AND. prc_has_s ) then
1243  start(2,3) = start(2,3) + 1
1244  start(2,4) = start(2,4) + 1
1245  endif
1246  endif
1247  start(3,:) = 1
1248  else
1249  start(:,:) = 1
1250  endif
1251 
1252  do k = 1, kmax
1253  axis(1:im,1:jm,k) = atmos_grid_cartesc_real_cz(k+ks-1,ims:ime,jms:jme)
1254  enddo
1255  axis_name(1:3) = (/'x ', 'y ', 'z '/)
1256  call file_history_set_associatedcoordinate( 'height', 'height above ground level', &
1257  'm', axis_name(1:3), axis(1:im,1:jm,1:kmax), start=start(:,1) )
1258 
1259  do k = 0, kmax
1260  axis(1:im,1:jm,k) = atmos_grid_cartesc_real_fz(k+ks-1,ims:ime,jms:jme)
1261  enddo
1262  axis_name(1:3) = (/'x ', 'y ', 'zh'/)
1263  call file_history_set_associatedcoordinate( 'height_xyw', 'height above ground level (half level xyw)', &
1264  'm' , axis_name(1:3), axis(1:im,1:jm,0:kmax), start=start(:,1) )
1265 
1266  do k = 1, kmax
1267  do j = 1, jm
1268  do i = 1, min(imh,ia-imsh)
1269  axis(i,j,k) = ( atmos_grid_cartesc_real_cz(k+ks-1,imsh+i-1,jms+j-1) + atmos_grid_cartesc_real_cz(k+ks-1,imsh+i,jms+j-1) ) * 0.5_rp
1270  enddo
1271  enddo
1272  enddo
1273  if ( imh == ia-imsh+1 ) then
1274  do k = 1, kmax
1275  do j = 1, jm
1276  axis(imh,j,k) = atmos_grid_cartesc_real_cz(k+ks-1,imsh+imh-1,jms+j-1)
1277  enddo
1278  enddo
1279  endif
1280  axis_name(1:3) = (/'xh', 'y ', 'z '/)
1281  call file_history_set_associatedcoordinate( 'height_uyz', 'height above ground level (half level uyz)', &
1282  'm', axis_name(1:3), axis(1:imh,1:jm,1:kmax), start=start(:,2) )
1283 
1284  do k = 1, kmax
1285  do j = 1, min(jmh,ja-jmsh)
1286  do i = 1, im
1287  axis(i,j,k) = ( atmos_grid_cartesc_real_cz(k+ks-1,ims+i-1,jmsh+j-1) + atmos_grid_cartesc_real_cz(k+ks-1,ims+i-1,jmsh+j) ) * 0.5_rp
1288  enddo
1289  enddo
1290  enddo
1291  if ( jmh == ja-jmsh+1 ) then
1292  do k = 1, kmax
1293  do i = 1, im
1294  axis(i,jmh,k) = atmos_grid_cartesc_real_cz(k+ks-1,ims+i-1,jmsh+jmh-1)
1295  enddo
1296  enddo
1297  endif
1298  axis_name(1:3) = (/'x ', 'yh', 'z '/)
1299  call file_history_set_associatedcoordinate( 'height_xvz', 'height above ground level (half level xvz)', &
1300  'm', axis_name(1:3), axis(1:im,1:jmh,1:kmax), start=start(:,3) )
1301 
1302  do k = 1, kmax
1303  do j = 1, min(jmh,ja-jmsh)
1304  do i = 1, min(imh,ia-imsh)
1305  axis(i,j,k) = ( atmos_grid_cartesc_real_cz(k+ks-1,imsh+i-1,jmsh+j-1) + atmos_grid_cartesc_real_cz(k+ks-1,imsh+i ,jmsh+j-1) &
1306  + atmos_grid_cartesc_real_cz(k+ks-1,imsh+i-1,jmsh+j ) + atmos_grid_cartesc_real_cz(k+ks-1,imsh+i ,jmsh+j ) ) * 0.25_rp
1307  enddo
1308  enddo
1309  enddo
1310  if ( jmh == ja-jmsh+1 ) then
1311  do k = 1, kmax
1312  do i = 1, min(imh,ia-imsh)
1313  axis(i,jmh,k) = ( atmos_grid_cartesc_real_cz(k+ks-1,imsh+i-1,jmsh+jmh-1) + atmos_grid_cartesc_real_cz(k+ks-1,imsh+i,jmsh+jmh-1) ) * 0.5_rp
1314  enddo
1315  enddo
1316  endif
1317  if ( imh == ia-imsh+1 ) then
1318  do k = 1, kmax
1319  do j = 1, min(jmh,ja-jmsh)
1320  axis(imh,j,k) = ( atmos_grid_cartesc_real_cz(k+ks-1,imsh+imh-1,jmsh+j-1) + atmos_grid_cartesc_real_cz(k+ks-1,imsh+imh-1,jmsh+j) ) * 0.5_rp
1321  enddo
1322  enddo
1323  endif
1324  if ( imh == ia-imsh+1 .AND. jmh == ja-jmsh+1 ) then
1325  do k = 1, kmax
1326  axis(imh,jmh,k) = atmos_grid_cartesc_real_cz(k+ks-1,imsh+imh-1,jmsh+jmh-1)
1327  enddo
1328  endif
1329  axis_name(1:3) = (/'xh', 'yh', 'z '/)
1330  call file_history_set_associatedcoordinate( 'height_uvz', 'height above ground level (half level uvz)', &
1331  'm', axis_name(1:3), axis(1:imh,1:jmh,1:kmax), start=start(:,4) )
1332 
1333  do k = 0, kmax
1334  do j = 1, jm
1335  do i = 1, min(imh,ia-imsh)
1336  axis(i,j,k) = ( atmos_grid_cartesc_real_fz(k+ks-1,imsh+i-1,jms+j-1) + atmos_grid_cartesc_real_fz(k+ks-1,imsh+i,jms+j-1) ) * 0.5_rp
1337  enddo
1338  enddo
1339  enddo
1340  if ( imh == ia-imsh+1 ) then
1341  do k = 0, kmax
1342  do j = 1, jm
1343  axis(imh,j,k) = atmos_grid_cartesc_real_fz(k+ks-1,imsh+imh-1,jms+j-1)
1344  enddo
1345  enddo
1346  endif
1347  axis_name(1:3) = (/'xh', 'y ', 'zh'/)
1348  call file_history_set_associatedcoordinate( 'height_uyw', 'height above ground level (half level uyw)', &
1349  'm', axis_name(1:3), axis(1:imh,1:jm,0:kmax), start=start(:,2) )
1350 
1351  do k = 0, kmax
1352  do j = 1, min(jmh,ja-jmsh)
1353  do i = 1, im
1354  axis(i,j,k) = ( atmos_grid_cartesc_real_fz(k+ks-1,ims+i-1,jmsh+j-1) + atmos_grid_cartesc_real_fz(k+ks-1,ims+i-1,jmsh+j) ) * 0.5_rp
1355  enddo
1356  enddo
1357  enddo
1358  if ( jmh == ja-jmsh+1 ) then
1359  do k = 0, kmax
1360  do i = 1, im
1361  axis(i,jmh,k) = atmos_grid_cartesc_real_fz(k+ks-1,ims+i-1,jmsh+jmh-1)
1362  enddo
1363  enddo
1364  endif
1365  axis_name(1:3) = (/'x ', 'yh', 'zh'/)
1366  call file_history_set_associatedcoordinate( 'height_xvw', 'height above ground level (half level xvw)', &
1367  'm', axis_name(1:3), axis(1:im,1:jmh,0:kmax), start=start(:,3) )
1368 
1369  do k = 0, kmax
1370  do j = 1, min(jmh,ja-jmsh)
1371  do i = 1, min(imh,ia-imsh)
1372  axis(i,j,k) = ( atmos_grid_cartesc_real_fz(k+ks-1,imsh+i-1,jmsh+j-1) + atmos_grid_cartesc_real_fz(k+ks-1,imsh+i ,jmsh+j-1) &
1373  + atmos_grid_cartesc_real_fz(k+ks-1,imsh+i-1,jmsh+j ) + atmos_grid_cartesc_real_fz(k+ks-1,imsh+i ,jmsh+j ) ) * 0.25_rp
1374  enddo
1375  enddo
1376  enddo
1377  if ( jmh == ja-jmsh+1 ) then
1378  do k = 0, kmax
1379  do i = 1, min(imh,ia-imsh)
1380  axis(i,jmh,k) = ( atmos_grid_cartesc_real_fz(k+ks-1,imsh+i-1,jmsh+jmh-1) + atmos_grid_cartesc_real_fz(k+ks-1,imsh+i,jmsh+jmh-1) ) * 0.5_rp
1381  enddo
1382  enddo
1383  endif
1384  if ( imh == ia-imsh+1 ) then
1385  do k = 0, kmax
1386  do j = 1, min(jmh,ja-jmsh)
1387  axis(imh,j,k) = ( atmos_grid_cartesc_real_fz(k+ks-1,imsh+imh-1,jmsh+j-1) + atmos_grid_cartesc_real_fz(k+ks-1,imsh+imh-1,jmsh+j) ) * 0.5_rp
1388  enddo
1389  enddo
1390  endif
1391  if ( imh == ia-imsh+1 .AND. jm == ja-jmsh+1 ) then
1392  do k = 0, kmax
1393  axis(imh,jmh,k) = atmos_grid_cartesc_real_fz(k+ks-1,imsh+imh-1,jmsh+jmh-1)
1394  enddo
1395  endif
1396  axis_name(1:3) = (/'xh', 'yh', 'zh'/)
1397  call file_history_set_associatedcoordinate( 'height_uvw', 'height above ground level (half level uvw)', 'm', &
1398  axis_name(1:3), axis(1:imh,1:jmh,0:kmax), start=start(:,4) )
1399 
1400  axis(1:im,1:jm,1) = atmos_grid_cartesc_real_lon(ims:ime,jms:jme) / d2r
1401  axis_name(1:2) = (/'x ', 'y '/)
1402  call file_history_set_associatedcoordinate( 'lon', 'longitude', 'degrees_east', &
1403  axis_name(1:2), axis(1:im,1:jm,1), start=start(:,1) )
1404 
1405  axis(1:imh,1:jm,1) = atmos_grid_cartesc_real_lonuy(imsh:ime,jms:jme) / d2r
1406  axis_name(1:2) = (/'xh', 'y '/)
1407  call file_history_set_associatedcoordinate( 'lon_uy', 'longitude (half level uy)', 'degrees_east', &
1408  axis_name(1:2), axis(1:imh,1:jm,1), start=start(:,2) )
1409 
1410  axis(1:im,1:jmh,1) = atmos_grid_cartesc_real_lonxv(ims:ime,jmsh:jme) / d2r
1411  axis_name(1:2) = (/'x ', 'yh'/)
1412  call file_history_set_associatedcoordinate( 'lon_xv', 'longitude (half level xv)', 'degrees_east', &
1413  axis_name(1:2), axis(1:im,1:jmh,1), start=start(:,3) )
1414 
1415  axis(1:imh,1:jmh,1) = atmos_grid_cartesc_real_lonuv(imsh:ime,jmsh:jme) / d2r
1416  axis_name(1:2) = (/'xh', 'yh'/)
1417  call file_history_set_associatedcoordinate( 'lon_uv', 'longitude (half level uv)', 'degrees_east', &
1418  axis_name(1:2), axis(1:imh,1:jmh,1), start=start(:,4) )
1419 
1420  axis(1:im,1:jm,1) = atmos_grid_cartesc_real_lat(ims:ime,jms:jme) / d2r
1421  axis_name(1:2) = (/'x ', 'y '/)
1422  call file_history_set_associatedcoordinate( 'lat', 'latitude', 'degrees_north', &
1423  axis_name(1:2), axis(1:im,1:jm,1), start=start(:,1) )
1424 
1425  axis(1:imh,1:jm,1) = atmos_grid_cartesc_real_latuy(imsh:ime,jms:jme) / d2r
1426  axis_name(1:2) = (/'xh', 'y '/)
1427  call file_history_set_associatedcoordinate( 'lat_uy', 'latitude (half level uy)', 'degrees_north', &
1428  axis_name(1:2), axis(1:imh,1:jm,1), start=start(:,2) )
1429 
1430  axis(1:im,1:jmh,1) = atmos_grid_cartesc_real_latxv(ims:ime,jmsh:jme) / d2r
1431  axis_name(1:2) = (/'x ', 'yh'/)
1432  call file_history_set_associatedcoordinate( 'lat_xv', 'latitude (half level xv)', 'degrees_north', &
1433  axis_name(1:2), axis(1:im,1:jmh,1), start=start(:,3) )
1434 
1435  axis(1:imh,1:jmh,1) = atmos_grid_cartesc_real_latuv(imsh:ime,jmsh:jme) / d2r
1436  axis_name(1:2) = (/'xh', 'yh'/)
1437  call file_history_set_associatedcoordinate( 'lat_uv', 'latitude (half level uv)', 'degrees_north', &
1438  axis_name(1:2), axis(1:imh,1:jmh,1), start=start(:,4) )
1439 
1440  axis_name(1:2) = (/'x ', 'y '/)
1441  call file_history_set_associatedcoordinate( 'topo', 'topography', 'm', axis_name(1:2), &
1442  topo_zsfc(ims:ime,jms:jme), start=start(:,1) )
1443 
1444  axis_name(1:2) = (/'x ', 'y '/)
1445  call file_history_set_associatedcoordinate( 'lsmask', 'fraction for land-sea mask', '1', axis_name(1:2), &
1446  landuse_frac_land(ims:ime,jms:jme), start=start(:,1) )
1447 
1448  axis_name(1:2) = (/'x ','y '/)
1449  call file_history_set_associatedcoordinate( 'cell_area', 'area of grid cell', 'm2', axis_name(1:2), &
1450  area(ims:ime,jms:jme), start=start(:,1) )
1451  axis_name(1:2) = (/'xh','y '/)
1452  call file_history_set_associatedcoordinate( 'cell_area_uy', 'area of grid cell (half level uy)', 'm2', axis_name(1:2), &
1453  areauy(imsh:ime,jms:jme), start=start(:,2) )
1454  axis_name(1:2) = (/'x ','yh'/)
1455  call file_history_set_associatedcoordinate( 'cell_area_xv', 'area of grid cell (half level xv)', 'm2', axis_name(1:2), &
1456  areaxv(ims:ime,jmsh:jme), start=start(:,3) )
1457 
1458  do k = 1, kmax
1459  do j = 1, jm
1460  do i = 1, imh
1461  axis(i,j,k) = areazuy_x(ks+k-1,imsh+i-1,jms+j-1)
1462  end do
1463  end do
1464  end do
1465  axis_name = (/'xh', 'y ', 'z '/)
1466  call file_history_set_associatedcoordinate( 'cell_area_uyz_x', 'area of grid cell face (half level uyz, normal x)', 'm2', &
1467  axis_name(1:3), axis(1:imh,1:jm,1:kmax), start=start(:,2) )
1468  do k = 1, kmax
1469  do j = 1, jmh
1470  do i = 1, im
1471  axis(i,j,k) = areazxv_y(ks+k-1,ims+i-1,jmsh+j-1)
1472  end do
1473  end do
1474  end do
1475  axis_name = (/'x ', 'yh', 'z '/)
1476  call file_history_set_associatedcoordinate( 'cell_area_xvz_y', 'area of grid cell face (half level xvz, normal y)', 'm2', &
1477  axis_name(1:3), axis(1:im,1:jmh,1:kmax), start=start(:,3) )
1478  do k = 0, kmax
1479  do j = 1, jmh
1480  do i = 1, imh
1481  axis(i,j,k) = areawuy_x(ks+k-1,imsh+i-1,jmsh+j-1)
1482  end do
1483  end do
1484  end do
1485  axis_name = (/'xh', 'y ', 'zh'/)
1486  call file_history_set_associatedcoordinate( 'cell_area_uyw_x', 'area of grid cell face (half level uyw, normal x)', 'm2', &
1487  axis_name(1:3), axis(1:imh,1:jmh,0:kmax), start=start(:,2) )
1488  do k = 0, kmax
1489  do j = 1, jmh
1490  do i = 1, im
1491  axis(i,j,k) = areawxv_y(ks+k-1,ims+i-1,jmsh+j-1)
1492  end do
1493  end do
1494  end do
1495  axis_name = (/'x ', 'yh', 'zh'/)
1496  call file_history_set_associatedcoordinate( 'cell_area_xvw_y', 'area of grid cell face (half level xvw, normal y)', 'm2', &
1497  axis_name(1:3), axis(1:im,1:jmh,0:kmax), start=start(:,3) )
1498  do k = 1, kmax
1499  do j = 1, jm
1500  do i = 1, im
1501  axis(i,j,k) = areazxy_x(ks+k-1,ims+i-1,jms+j-1)
1502  end do
1503  end do
1504  end do
1505  axis_name = (/'x ', 'y ', 'z '/)
1506  call file_history_set_associatedcoordinate( 'cell_area_xyz_x', 'area of grid cell face (half level xyz, normal x)', 'm2', &
1507  axis_name(1:3), axis(1:im,1:jm,1:kmax), start=start(:,1) )
1508  do k = 1, kmax
1509  do j = 1, jmh
1510  do i = 1, imh
1511  axis(i,j,k) = areazuv_y(ks+k-1,imsh+i-1,jmsh+j-1)
1512  end do
1513  end do
1514  end do
1515  axis_name = (/'xh', 'yh', 'z '/)
1516  call file_history_set_associatedcoordinate( 'cell_area_uvz_y', 'area of grid cell face (half level uvz, normal y)', 'm2', &
1517  axis_name(1:3), axis(1:imh,1:jmh,1:kmax), start=start(:,4) )
1518  do k = 1, kmax
1519  do j = 1, jmh
1520  do i = 1, imh
1521  axis(i,j,k) = areazuv_x(ks+k-1,imsh+i-1,jmsh+j-1)
1522  end do
1523  end do
1524  end do
1525  axis_name = (/'xh', 'yh', 'z '/)
1526  call file_history_set_associatedcoordinate( 'cell_area_uvz_x', 'area of grid cell face (half level uvz, normal x)', 'm2', &
1527  axis_name(1:3), axis(1:imh,1:jmh,1:kmax), start=start(:,4) )
1528  do k = 1, kmax
1529  do j = 1, jm
1530  do i = 1, im
1531  axis(i,j,k) = areazxy_y(ks+k-1,ims+i-1,jms+j-1)
1532  end do
1533  end do
1534  end do
1535  axis_name = (/'x ', 'y ', 'z '/)
1536  call file_history_set_associatedcoordinate( 'cell_area_xyz_y', 'area of grid cell face (half level xyz, normal y)', 'm2', &
1537  axis_name(1:3), axis(1:im,1:jm,1:kmax), start=start(:,1) )
1538 
1539  do k = 1, kmax
1540  do j = 1, jm
1541  do i = 1, im
1542  axis(i,j,k) = vol(ks+k-1,ims+i-1,jms+j-1)
1543  end do
1544  end do
1545  end do
1546  axis_name = (/ 'x ', 'y ', 'z '/)
1547  call file_history_set_associatedcoordinate( 'cell_volume', 'volume of grid cell', 'm3', &
1548  axis_name(1:3), axis(1:im,1:jm,1:kmax), start=start(:,1) )
1549  do k = 0, kmax
1550  do j = 1, jm
1551  do i = 1, im
1552  axis(i,j,k) = volwxy(ks+k-1,ims+i-1,jms+j-1)
1553  end do
1554  end do
1555  end do
1556  axis_name = (/'x ', 'y ', 'zh'/)
1557  call file_history_set_associatedcoordinate( 'cell_volume_xyw', 'volume of grid cell (half level xyw)', 'm3', &
1558  axis_name(1:3), axis(1:im,1:jm,0:kmax), start=start(:,1) )
1559  do k = 1, kmax
1560  do j = 1, jm
1561  do i = 1, imh
1562  axis(i,j,k) = volzuy(ks+k-1,imsh+i-1,jms+j-1)
1563  end do
1564  end do
1565  end do
1566  axis_name = (/'xh', 'y ', 'z '/)
1567  call file_history_set_associatedcoordinate( 'cell_volume_uyz', 'volume of grid cell (half level uyz)', 'm3', &
1568  axis_name(1:3), axis(1:imh,1:jm,1:kmax), start=start(:,2) )
1569  do k = 1, kmax
1570  do j = 1, jmh
1571  do i = 1, im
1572  axis(i,j,k) = volzxv(ks+k-1,ims+i-1,jmsh+j-1)
1573  end do
1574  end do
1575  end do
1576  axis_name = (/'x ', 'yh', 'z '/)
1577  call file_history_set_associatedcoordinate( 'cell_volume_xvz', 'volume of grid cell (half level xvz)', 'm3', &
1578  axis_name(1:3), axis(1:im,1:jmh,1:kmax), start=start(:,3) )
1579 
1580  if ( okmax > 0 ) then
1581  do k = 1, okmax
1582  do j = 1, jm
1583  do i = 1, im
1584  axiso(i,j,k) = volo(oks+k-1,ims+i-1,jms+j-1)
1585  end do
1586  end do
1587  end do
1588  axis_name = (/'x ', 'y ', 'oz'/)
1589  call file_history_set_associatedcoordinate( 'cell_volume_xyo', 'volume of grid cell', 'm3', &
1590  axis_name(1:3), axiso(:,:,:), start=start(:,1) )
1591  endif
1592 
1593  if ( lkmax > 0 ) then
1594  do k = 1, lkmax
1595  do j = 1, jm
1596  do i = 1, im
1597  axisl(i,j,k) = voll(lks+k-1,ims+i-1,jms+j-1)
1598  end do
1599  end do
1600  end do
1601  axis_name = (/'x ', 'y ', 'lz'/)
1602  call file_history_set_associatedcoordinate( 'cell_volume_xyl', 'volume of grid cell', 'm3', &
1603  axis_name(1:3), axisl(:,:,:), start=start(:,1) )
1604  endif
1605 
1606  if ( ukmax > 0 ) then
1607  do k = 1, ukmax
1608  do j = 1, jm
1609  do i = 1, im
1610  axisu(i,j,k) = volu(uks+k-1,ims+i-1,jms+j-1)
1611  end do
1612  end do
1613  end do
1614  axis_name = (/'x ', 'y ', 'uz'/)
1615  call file_history_set_associatedcoordinate( 'cell_volume_xyu', 'volume of grid cell', 'm3', &
1616  axis_name(1:3), axisu(:,:,:), start=start(:,1) )
1617  endif
1618 
1619  return
1620  end subroutine file_history_cartesc_set_axes
1621 
1622  !-----------------------------------------------------------------------------
1623  subroutine file_history_cartesc_set_axes_attributes
1624  use scale_atmos_grid_cartesc, only: &
1626  use scale_calendar, only: &
1628  use scale_file_history, only: &
1630  file_history_set_attribute
1631  use scale_prc, only: &
1632  prc_myrank
1633  use scale_const, only: &
1634  undef => const_undef
1635  use scale_prc_cartesc, only: &
1636  prc_2drank, &
1637  prc_num_x, &
1638  prc_num_y, &
1639  prc_periodic_x, &
1640  prc_periodic_y, &
1641  prc_has_w, &
1642  prc_has_e, &
1643  prc_has_s, &
1644  prc_has_n
1645  use scale_file, only: &
1647  use scale_file_cartesc, only: &
1648  axisattinfo, &
1649  mappinginfo
1650  use scale_mapprojection, only: &
1652  implicit none
1653 
1654  character(len=34) :: tunits
1655  character(len=H_SHORT) :: calendar
1656 
1657  type(axisattinfo) :: ainfo(4) ! x, xh, y, yh
1658  type(mappinginfo) :: minfo
1659  !---------------------------------------------------------------------------
1660 
1661  call file_history_set_attribute( "global", "Conventions", "CF-1.6" ) ! [IN]
1662 
1663  call file_history_set_attribute( "global", "grid_name", atmos_grid_cartesc_name ) ! [IN]
1664 
1665  if ( file_history_aggregate ) then
1666  call file_history_set_attribute( "global", "scale_cartesC_prc_rank_x", (/0/) ) ! [IN]
1667  call file_history_set_attribute( "global", "scale_cartesC_prc_rank_y", (/0/) ) ! [IN]
1668 
1669  call file_history_set_attribute( "global", "scale_cartesC_prc_num_x", (/1/) ) ! [IN]
1670  call file_history_set_attribute( "global", "scale_cartesC_prc_num_y", (/1/) ) ! [IN]
1671  else
1672  call file_history_set_attribute( "global", "scale_cartesC_prc_rank_x", (/prc_2drank(prc_myrank,1)/) ) ! [IN]
1673  call file_history_set_attribute( "global", "scale_cartesC_prc_rank_y", (/prc_2drank(prc_myrank,2)/) ) ! [IN]
1674 
1675  call file_history_set_attribute( "global", "scale_cartesC_prc_num_x", (/prc_num_x/) ) ! [IN]
1676  call file_history_set_attribute( "global", "scale_cartesC_prc_num_y", (/prc_num_y/) ) ! [IN]
1677  endif
1678 
1679  call file_history_set_attribute( "global", "scale_cartesC_prc_periodic_z", .false. ) ! [IN]
1680  call file_history_set_attribute( "global", "scale_cartesC_prc_periodic_x", prc_periodic_x ) ! [IN]
1681  call file_history_set_attribute( "global", "scale_cartesC_prc_periodic_y", prc_periodic_y ) ! [IN]
1682 
1683  call file_history_set_attribute( "global", "scale_atmos_grid_cartesC_index_imaxg", (/imaxg/) ) ! [IN]
1684  call file_history_set_attribute( "global", "scale_atmos_grid_cartesC_index_jmaxg", (/jmaxg/) ) ! [IN]
1685 
1686  call file_history_set_attribute( "global", "scale_atmos_grid_cartesC_index_kmax", (/kmax/) ) ! [IN]
1687  if ( okmax > 0 ) call file_history_set_attribute( "global", "scale_ocean_grid_cartesC_index_kmax", (/okmax/) ) ! [IN]
1688  if ( lkmax > 0 ) call file_history_set_attribute( "global", "scale_land_grid_cartesC_index_kmax", (/lkmax/) ) ! [IN]
1689  if ( ukmax > 0 ) call file_history_set_attribute( "global", "scale_urban_grid_cartesC_index_kmax", (/ukmax/) ) ! [IN]
1690 
1691  call file_history_set_attribute( "global", "scale_atmos_grid_cartesC_index_khalo", (/khalo/) ) ! [IN]
1692  call file_history_set_attribute( "global", "scale_atmos_grid_cartesC_index_ihalo", (/ihalo/) ) ! [IN]
1693  call file_history_set_attribute( "global", "scale_atmos_grid_cartesC_index_jhalo", (/jhalo/) ) ! [IN]
1694 
1695  call calendar_get_name( calendar )
1696  if ( calendar /= "" ) call file_history_set_attribute( "global", "calendar", calendar )
1697  call file_get_cftunits( file_history_cartesc_startdate(:), tunits )
1698  call file_history_set_attribute( "global", "time_units", tunits )
1699  call file_history_set_attribute( "global", "time_start", (/file_history_cartesc_startms/) )
1700 
1701  if ( prc_periodic_x ) then
1702  ainfo(1)%periodic = .true.
1703  ainfo(2)%periodic = .true.
1704  else
1705  ainfo(1)%periodic = .false.
1706  ainfo(2)%periodic = .false.
1707  endif
1708 
1709  if ( prc_periodic_y ) then
1710  ainfo(3)%periodic = .true.
1711  ainfo(4)%periodic = .true.
1712  else
1713  ainfo(3)%periodic = .false.
1714  ainfo(4)%periodic = .false.
1715  endif
1716 
1717  ! for x
1718  if ( prc_periodic_x .OR. .NOT. file_history_cartesc_boundary ) then
1719  ainfo(1)%size_global (1) = imax * prc_num_x
1720  ainfo(1)%start_global(1) = is_ing - ihalo
1721  ainfo(1)%halo_global (1) = 0 ! west side
1722  ainfo(1)%halo_global (2) = 0 ! east side
1723  ainfo(1)%halo_local (1) = 0 ! west side
1724  ainfo(1)%halo_local (2) = 0 ! east side
1725  else
1726  ainfo(1)%size_global (1) = iag
1727  ainfo(1)%start_global(1) = isga
1728  ainfo(1)%halo_global (1) = ihalo ! west side
1729  ainfo(1)%halo_global (2) = ihalo ! east side
1730  ainfo(1)%halo_local (1) = ihalo ! west side
1731  ainfo(1)%halo_local (2) = ihalo ! east side
1732  if ( .not. file_history_aggregate ) then
1733  if( prc_has_w ) ainfo(1)%halo_local(1) = 0
1734  if( prc_has_e ) ainfo(1)%halo_local(2) = 0
1735  end if
1736  endif
1737 
1738  ! for xh
1739  ainfo(2) = ainfo(1)
1740  if ( .NOT. prc_periodic_x .AND. .NOT. file_history_cartesc_boundary ) then
1741  ainfo(2)%size_global (1) = ainfo(2)%size_global (1) + 1
1742  ainfo(2)%halo_global (1) = ainfo(2)%halo_global (1) + 1
1743  if ( prc_has_w .and. ( .not. file_history_aggregate ) ) then
1744  ainfo(2)%start_global(1) = ainfo(2)%start_global(1) + 1
1745  else
1746  ainfo(2)%halo_local (1) = ainfo(2)%halo_local (1) + 1
1747  endif
1748  endif
1749 
1750  ! for y
1751  if ( prc_periodic_y .OR. .NOT. file_history_cartesc_boundary ) then
1752  ainfo(3)%size_global (1) = jmax * prc_num_y
1753  ainfo(3)%start_global(1) = js_ing - jhalo
1754  ainfo(3)%halo_global (1) = 0 ! south side
1755  ainfo(3)%halo_global (2) = 0 ! north side
1756  ainfo(3)%halo_local (1) = 0 ! south side
1757  ainfo(3)%halo_local (2) = 0 ! north side
1758  else
1759  ainfo(3)%size_global (1) = jag
1760  ainfo(3)%start_global(1) = jsga
1761  ainfo(3)%halo_global (1) = jhalo ! south side
1762  ainfo(3)%halo_global (2) = jhalo ! north side
1763  ainfo(3)%halo_local (1) = jhalo ! south side
1764  ainfo(3)%halo_local (2) = jhalo ! north side
1765  if ( .not. file_history_aggregate ) then
1766  if( prc_has_s ) ainfo(3)%halo_local(1) = 0
1767  if( prc_has_n ) ainfo(3)%halo_local(2) = 0
1768  end if
1769  endif
1770 
1771  ! for yh
1772  ainfo(4) = ainfo(3)
1773  if ( .NOT. prc_periodic_y .AND. .NOT. file_history_cartesc_boundary ) then
1774  ainfo(4)%size_global (1) = ainfo(4)%size_global (1) + 1
1775  ainfo(4)%halo_global (1) = ainfo(4)%halo_global (1) + 1
1776  if ( prc_has_s .and. ( .not. file_history_aggregate ) ) then
1777  ainfo(4)%start_global(1) = ainfo(4)%start_global(1) + 1
1778  else
1779  ainfo(4)%halo_local (1) = ainfo(4)%halo_local (1) + 1
1780  endif
1781  endif
1782 
1783  if ( file_history_aggregate ) then
1784  ainfo(1)%start_global(1) = 1
1785  ainfo(2)%start_global(1) = 1
1786  ainfo(3)%start_global(1) = 1
1787  ainfo(4)%start_global(1) = 1
1788  end if
1789 
1790  call file_history_set_attribute( "x" , "size_global" , ainfo(1)%size_global (:) )
1791  call file_history_set_attribute( "x" , "start_global", ainfo(1)%start_global(:) )
1792  call file_history_set_attribute( "x" , "halo_global" , ainfo(1)%halo_global (:) )
1793  call file_history_set_attribute( "x" , "halo_local" , ainfo(1)%halo_local (:) )
1794  call file_history_set_attribute( "x" , "periodic" , ainfo(1)%periodic )
1795 
1796  call file_history_set_attribute( "xh", "size_global" , ainfo(2)%size_global (:) )
1797  call file_history_set_attribute( "xh", "start_global", ainfo(2)%start_global(:) )
1798  call file_history_set_attribute( "xh", "halo_global" , ainfo(2)%halo_global (:) )
1799  call file_history_set_attribute( "xh", "halo_local" , ainfo(2)%halo_local (:) )
1800  call file_history_set_attribute( "xh", "periodic" , ainfo(2)%periodic )
1801 
1802  call file_history_set_attribute( "y" , "size_global" , ainfo(3)%size_global (:) )
1803  call file_history_set_attribute( "y" , "start_global", ainfo(3)%start_global(:) )
1804  call file_history_set_attribute( "y" , "halo_global" , ainfo(3)%halo_global (:) )
1805  call file_history_set_attribute( "y" , "halo_local" , ainfo(3)%halo_local (:) )
1806  call file_history_set_attribute( "y" , "periodic" , ainfo(3)%periodic )
1807 
1808  call file_history_set_attribute( "yh", "size_global" , ainfo(4)%size_global (:) )
1809  call file_history_set_attribute( "yh", "start_global", ainfo(4)%start_global(:) )
1810  call file_history_set_attribute( "yh", "halo_global" , ainfo(4)%halo_global (:) )
1811  call file_history_set_attribute( "yh", "halo_local" , ainfo(4)%halo_local (:) )
1812  call file_history_set_attribute( "yh", "periodic" , ainfo(4)%periodic )
1813 
1814  ! map projection info
1815  call mapprojection_get_attributes( minfo%mapping_name, & ! [OUT]
1816  minfo%false_easting (1), & ! [OUT]
1817  minfo%false_northing (1), & ! [OUT]
1818  minfo%longitude_of_central_meridian (1), & ! [OUT]
1819  minfo%longitude_of_projection_origin (1), & ! [OUT]
1820  minfo%latitude_of_projection_origin (1), & ! [OUT]
1821  minfo%straight_vertical_longitude_from_pole(1), & ! [OUT]
1822  minfo%standard_parallel (:) ) ! [OUT]
1823 
1824  if ( minfo%mapping_name /= "" ) then
1825  call file_history_set_attribute( "x" , "standard_name", "projection_x_coordinate" )
1826  call file_history_set_attribute( "xh", "standard_name", "projection_x_coordinate" )
1827  call file_history_set_attribute( "y" , "standard_name", "projection_y_coordinate" )
1828  call file_history_set_attribute( "yh", "standard_name", "projection_y_coordinate" )
1829 
1830  call file_history_set_attribute( minfo%mapping_name, "grid_mapping_name", minfo%mapping_name, add_variable=.true. )
1831 
1832  if ( minfo%false_easting(1) /= undef ) then
1833  call file_history_set_attribute( minfo%mapping_name, & ! [IN]
1834  "false_easting", & ! [IN]
1835  minfo%false_easting(:) ) ! [IN]
1836  endif
1837 
1838  if ( minfo%false_northing(1) /= undef ) then
1839  call file_history_set_attribute( minfo%mapping_name, & ! [IN]
1840  "false_northing", & ! [IN]
1841  minfo%false_northing(:) ) ! [IN]
1842  endif
1843 
1844  if ( minfo%longitude_of_central_meridian(1) /= undef ) then
1845  call file_history_set_attribute( minfo%mapping_name, & ! [IN]
1846  "longitude_of_central_meridian", & ! [IN]
1847  minfo%longitude_of_central_meridian(:) ) ! [IN]
1848  endif
1849 
1850  if ( minfo%longitude_of_projection_origin(1) /= undef ) then
1851  call file_history_set_attribute( minfo%mapping_name, & ! [IN]
1852  "longitude_of_projection_origin", & ! [IN]
1853  minfo%longitude_of_projection_origin(:) ) ! [IN]
1854  endif
1855 
1856  if ( minfo%latitude_of_projection_origin(1) /= undef ) then
1857  call file_history_set_attribute( minfo%mapping_name, & ! [IN]
1858  "latitude_of_projection_origin", & ! [IN]
1859  minfo%latitude_of_projection_origin(:) ) ! [IN]
1860  endif
1861 
1862  if ( minfo%straight_vertical_longitude_from_pole(1) /= undef ) then
1863  call file_history_set_attribute( minfo%mapping_name, & ! [IN]
1864  "straight_vertical_longitude_from_pole", & ! [IN]
1865  minfo%straight_vertical_longitude_from_pole(:) ) ! [IN]
1866  endif
1867 
1868  if ( minfo%standard_parallel(1) /= undef ) then
1869  if ( minfo%standard_parallel(2) /= undef ) then
1870  call file_history_set_attribute( minfo%mapping_name, & ! [IN]
1871  "standard_parallel", & ! [IN]
1872  minfo%standard_parallel(1:2) ) ! [IN]
1873  else
1874  call file_history_set_attribute( minfo%mapping_name, & ! [IN]
1875  "standard_parallel", & ! [IN]
1876  minfo%standard_parallel(1:1) ) ! [IN]
1877  endif
1878  endif
1879  endif
1880 
1881  ! area and volume
1882  call file_history_set_attribute( "cell_area", "standard_name", "area" ) ! [IN]
1883  call file_history_set_attribute( "cell_area_uy", "standard_name", "area" ) ! [IN]
1884  call file_history_set_attribute( "cell_area_xv", "standard_name", "area" ) ! [IN]
1885 
1886  call file_history_set_attribute( "cell_area_uyz_x", "standard_name", "area" ) ! [IN]
1887  call file_history_set_attribute( "cell_area_xvz_y", "standard_name", "area" ) ! [IN]
1888  call file_history_set_attribute( "cell_area_uyw_x", "standard_name", "area" ) ! [IN]
1889  call file_history_set_attribute( "cell_area_xvw_y", "standard_name", "area" ) ! [IN]
1890  call file_history_set_attribute( "cell_area_xyz_x", "standard_name", "area" ) ! [IN]
1891  call file_history_set_attribute( "cell_area_uvz_y", "standard_name", "area" ) ! [IN]
1892  call file_history_set_attribute( "cell_area_uvz_x", "standard_name", "area" ) ! [IN]
1893  call file_history_set_attribute( "cell_area_xyz_y", "standard_name", "area" ) ! [IN]
1894 
1895  call file_history_set_attribute( "cell_volume", "standard_name", "volume" ) ! [IN]
1896  call file_history_set_attribute( "cell_volume_xyw", "standard_name", "volume" ) ! [IN]
1897  call file_history_set_attribute( "cell_volume_uyz", "standard_name", "volume" ) ! [IN]
1898  call file_history_set_attribute( "cell_volume_xvz", "standard_name", "volume" ) ! [IN]
1899 
1900  if ( okmax > 0 ) then
1901  call file_history_set_attribute( "cell_volume_xyo", "standard_name", "volume" ) ! [IN]
1902  endif
1903  if ( lkmax > 0 ) then
1904  call file_history_set_attribute( "cell_volume_xyl", "standard_name", "volume" ) ! [IN]
1905  endif
1906  if ( ukmax > 0 ) then
1907  call file_history_set_attribute( "cell_volume_xyu", "standard_name", "volume" ) ! [IN]
1908  endif
1909 
1910  ! SGRID
1911  call file_history_set_attribute( "grid", "cf_role", "grid_topology", add_variable=.true. )
1912  call file_history_set_attribute( "grid", "topology_dimension", (/ 2 /) )
1913  call file_history_set_attribute( "grid", "node_dimensions", "xh yh" )
1914  call file_history_set_attribute( "grid", "face_dimensions", "x: xh (padding: none) y: yh (padding: none)" )
1915  call file_history_set_attribute( "grid", "node_coordinates", "lon_uv lat_uv" )
1916  call file_history_set_attribute( "grid", "face_coordinates", "lon lat" )
1917  call file_history_set_attribute( "grid", "edge1_coordinates", "lon_uy lat_uy" )
1918  call file_history_set_attribute( "grid", "edge2_coordinates", "lon_xv lat_xv" )
1919  call file_history_set_attribute( "grid", "vertical_dimensions", "z: zh (padding: none)" )
1920 
1921  call file_history_set_attribute( "grid_ocean", "cf_role", "grid_topology", add_variable=.true. )
1922  call file_history_set_attribute( "grid_ocean", "topology_dimension", (/ 2 /) )
1923  call file_history_set_attribute( "grid_ocean", "node_dimensions", "xh yh" )
1924  call file_history_set_attribute( "grid_ocean", "face_dimensions", "x: xh (padding: none) y: yh (padding: none)" )
1925  call file_history_set_attribute( "grid_ocean", "node_coordinates", "lon_uv lat_uv" )
1926  call file_history_set_attribute( "grid_ocean", "face_coordinates", "lon lat" )
1927  call file_history_set_attribute( "grid_ocean", "edge1_coordinates", "lon_uy lat_uy" )
1928  call file_history_set_attribute( "grid_ocean", "edge2_coordinates", "lon_xv lat_xv" )
1929  call file_history_set_attribute( "grid_ocean", "vertical_dimensions", "oz: ozh (padding: none)" )
1930 
1931  call file_history_set_attribute( "grid_land", "cf_role", "grid_topology", add_variable=.true. )
1932  call file_history_set_attribute( "grid_land", "topology_dimension", (/ 2 /) )
1933  call file_history_set_attribute( "grid_land", "node_dimensions", "xh yh" )
1934  call file_history_set_attribute( "grid_land", "face_dimensions", "x: xh (padding: none) y: yh (padding: none)" )
1935  call file_history_set_attribute( "grid_land", "node_coordinates", "lon_uv lat_uv" )
1936  call file_history_set_attribute( "grid_land", "face_coordinates", "lon lat" )
1937  call file_history_set_attribute( "grid_land", "edge1_coordinates", "lon_uy lat_uy" )
1938  call file_history_set_attribute( "grid_land", "edge2_coordinates", "lon_xv lat_xv" )
1939  call file_history_set_attribute( "grid_land", "vertical_dimensions", "lz: lzh (padding: none)" )
1940 
1941  call file_history_set_attribute( "grid_urban", "cf_role", "grid_topology", add_variable=.true. )
1942  call file_history_set_attribute( "grid_urban", "topology_dimension", (/ 2 /) )
1943  call file_history_set_attribute( "grid_urban", "node_dimensions", "xh yh" )
1944  call file_history_set_attribute( "grid_urban", "face_dimensions", "x: xh (padding: none) y: yh (padding: none)" )
1945  call file_history_set_attribute( "grid_urban", "node_coordinates", "lon_uv lat_uv" )
1946  call file_history_set_attribute( "grid_urban", "face_coordinates", "lon lat" )
1947  call file_history_set_attribute( "grid_urban", "edge1_coordinates", "lon_uy lat_uy" )
1948  call file_history_set_attribute( "grid_urban", "edge2_coordinates", "lon_xv lat_xv" )
1949  call file_history_set_attribute( "grid_urban", "vertical_dimensions", "uz: uzh (padding: none)" )
1950 
1951  call file_history_set_attribute( "grid_pressure", "cf_role", "grid_topology", add_variable=.true. )
1952  call file_history_set_attribute( "grid_pressure", "topology_dimension", (/ 2 /) )
1953  call file_history_set_attribute( "grid_pressure", "node_dimensions", "xh yh" )
1954  call file_history_set_attribute( "grid_pressure", "face_dimensions", "x: xh (padding: none) y: yh (padding: none)" )
1955  call file_history_set_attribute( "grid_pressure", "node_coordinates", "lon_uv lat_uv" )
1956  call file_history_set_attribute( "grid_pressure", "face_coordinates", "lon lat" )
1957  call file_history_set_attribute( "grid_pressure", "edge1_coordinates", "lon_uy lat_uy" )
1958  call file_history_set_attribute( "grid_pressure", "edge2_coordinates", "lon_xv lat_xv" )
1959  call file_history_set_attribute( "grid_pressure", "vertical_dimensions", "pressure" )
1960 
1961  call file_history_set_attribute( "grid_z", "cf_role", "grid_topology", add_variable=.true. )
1962  call file_history_set_attribute( "grid_z", "topology_dimension", (/ 2 /) )
1963  call file_history_set_attribute( "grid_z", "node_dimensions", "xh yh" )
1964  call file_history_set_attribute( "grid_z", "face_dimensions", "x: xh (padding: none) y: yh (padding: none)" )
1965  call file_history_set_attribute( "grid_z", "node_coordinates", "lon_uv lat_uv" )
1966  call file_history_set_attribute( "grid_z", "face_coordinates", "lon lat" )
1967  call file_history_set_attribute( "grid_z", "edge1_coordinates", "lon_uy lat_uy" )
1968  call file_history_set_attribute( "grid_z", "edge2_coordinates", "lon_xv lat_xv" )
1969  call file_history_set_attribute( "grid_z", "vertical_dimensions", "height_xyw: height (padding: none)" )
1970 
1971  call file_history_set_attribute( "grid_model", "cf_role", "grid_topology", add_variable=.true. )
1972  call file_history_set_attribute( "grid_model", "topology_dimension", (/ 2 /) )
1973  call file_history_set_attribute( "grid_model", "node_dimensions", "FX FY" )
1974  call file_history_set_attribute( "grid_model", "face_dimensions", "CX: FY (padding: none) CY: FY (padding: none)" )
1975  call file_history_set_attribute( "grid_model", "vertical_dimensions", "CZ: FZ (padding: none)" )
1976 
1977  call file_history_set_attribute( "grid_model_global", "cf_role", "grid_topology", add_variable=.true. )
1978  call file_history_set_attribute( "grid_model_global", "topology_dimension", (/ 2 /) )
1979  call file_history_set_attribute( "grid_model_global", "node_dimensions", "FXG FYG" )
1980  call file_history_set_attribute( "grid_model_global", "face_dimensions", "CXG: FYG (padding: none) CYG: FYG (padding: none)" )
1981  call file_history_set_attribute( "grid_model_global", "vertical_dimensions", "CZ: FZ (padding: none)" )
1982 
1983  return
1984  end subroutine file_history_cartesc_set_axes_attributes
1985 
1986 end module scale_file_history_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.
integer, public iagb
of computational grids
integer, public time_nowstep
current step [number]
Definition: scale_time.F90:74
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cdy
y-length of control volume [m]
subroutine, public interp_vert_xi2p(Kpres, KA, IA, IS, IE, JA, JS, JE, var, var_P)
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areawuy_x
virtical area (wuy, normal x) [m2]
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
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, public file_history_setup(title, source, institution, time_start, time_interval, time_units, time_since, calendar, default_basename, default_postfix_timelabel, default_zcoord, default_tinterval, default_tunit, default_taverage, default_datatype, myrank)
Setup.
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]
integer, parameter, public khalo
of halo cells: z
integer, public jsgb
start point of the inner domain: y, global
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lonuv
longitude at staggered point (uv) [rad,0-2pi]
real(dp), public time_nowms
subsecond part of current time [millisec]
Definition: scale_time.F90:70
subroutine, public file_history_set_dim(name, ndims, nzcoords, dims, zcoords, start, count, mapping, area, area_x, area_y, volume, location, grid)
set dimension information
real(rp), dimension(:,:,:), allocatable, public ocean_grid_cartesc_real_vol
volume of grid cell
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
module land / grid / cartesianC / real
module land / grid / cartesianC / index
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_areaxv
horizontal area ( xv, normal z) [m2]
integer, public iag
of computational grids
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_areauy
horizontal area ( uy, normal z) [m2]
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cbfxg
center buffer factor (0-1): x, global
subroutine file_history_cartesc_truncate_1d(src, dim_type, zcoord, fill_halo, dst)
truncate 1D data to history buffer
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lat
latitude [rad,-pi,pi]
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cbfz
center buffer factor (0-1): z
logical, public interp_available
topography exists & vertical interpolation has meaning?
real(dp), public time_startdaysec
second of start time [sec]
Definition: scale_time.F90:78
module INTERPOLATION vertical
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_vol
control volume (zxy) [m3]
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fxg
face coordinate [m]: x, global
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areawxv_y
virtical area (wxv, normal y) [m2]
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fz
geopotential height [m] (wxy)
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
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volzxv
control volume (zxv) [m3]
subroutine, public interp_vert_xi2z(KA, KS, KE, IA, IS, IE, JA, JS, JE, Xi, Z, var, var_Z)
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdz
z-length of grid(i+1) to grid(i) [m]
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
integer, public isgb
start point of the inner domain: x, global
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazuy_x
virtical area (zuy, normal x) [m2]
subroutine, public file_history_cartesc_set_pres(PRES, PRESH, SFC_PRES)
set hydrostatic pressure for pressure coordinate
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]
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lon
longitude [rad,0-2pi]
logical, public prc_has_n
logical, public prc_has_e
logical, public prc_periodic_y
periodic condition or not (Y)?
module urban / grid / icosahedralA / index
subroutine, public file_history_set_axis(name, desc, units, dim, var, bounds, down, gsize, start)
set axis information
integer, public jmaxg
of computational cells: y, global
real(rp), public const_undef
Definition: scale_const.F90:41
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cy
center coordinate [m]: y, local
logical, public prc_periodic_x
periodic condition or not (X)?
integer, public is
start point of inner domain: x, local
real(rp), dimension(:,:,:), allocatable, public urban_grid_cartesc_real_vol
volume of grid cell
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
integer, public js_ing
start point of the inner domain: cy, global
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
module LANDUSE
subroutine, public calendar_get_name(name)
real(dp), public time_dtsec
time interval of model [sec]
Definition: scale_time.F90:38
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_latuy
latitude at staggered point (uy) [rad,-pi,pi]
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
module ocean / grid / cartesianC / real
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volwxy
control volume (wxy) [m3]
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
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]
integer, parameter, public file_hshort
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
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
integer, parameter, public prc_masterrank
master process in each communicator
Definition: scale_prc.F90:65
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lonxv
longitude at staggered point (xv) [rad,0-2pi]
integer, public ks
start point of inner domain: z, local
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_lonuy
longitude at staggered point (uy) [rad,0-2pi]
subroutine, public interp_vert_alloc_pres(Kpres, IA, JA)
Setup.
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
logical, public file_history_aggregate
integer, public kmax
of computational cells: z, local
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazxy_y
virtical area (zxy, normal y) [m2]
subroutine, public interp_vert_xih2zh(KA, KS, KE, IA, IS, IE, JA, JS, JE, Xih, Zh, var, var_Z)
subroutine, public interp_vert_setcoef_pres(Kpres, KA, KS, KE, IA, IS, IE, JA, JS, JE, PRES, PRESh, SFC_PRES, Paxis)
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
subroutine file_history_cartesc_truncate_3d(src, dim_type, zcoord, fill_halo, dst)
truncate 3D data to history buffer
integer, public jag
of computational grids
procedure(truncate_2d), pointer, public file_history_truncate_2d
module CONSTANT
Definition: scale_const.F90:11
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fy
face coordinate [m]: y, local
real(dp), parameter, public file_rmiss
integer, public js
start point of inner domain: y, local
subroutine, public file_history_cartesc_setup
Setup.
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fbfx
face buffer factor (0-1): x
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cbfy
center buffer factor (0-1): y
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
integer, public jagb
of computational grids
module ocean / grid / cartesianC / index
integer, public imaxg
of computational cells: x, global
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_cz
geopotential height [m] (zxy)
module profiler
Definition: scale_prof.F90:11
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazxy_x
virtical area (zxy, normal x) [m2]
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cbfyg
center buffer factor (0-1): y, global
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fbfz
face buffer factor (0-1): z
character(len=7), parameter, public atmos_grid_cartesc_name
module Atmosphere GRID CartesC Real(real space)
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fbfy
face buffer factor (0-1): y
module Map projection
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_area
horizontal area ( xy, normal z) [m2]
subroutine, public interp_vert_xih2p(Kpres, KA, IA, IS, IE, JA, JS, JE, var, var_P)
module PRECISION
module file / cartesianC
real(rp), dimension(:,:), allocatable, public topo_zsfc
absolute ground height [m]
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
module TOPOGRAPHY
module urban / grid / cartesianC / real
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fyg
face coordinate [m]: y, global
procedure(truncate_1d), pointer, public file_history_truncate_1d
module CALENDAR
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_latuv
latitude at staggered point (uv) [rad,-pi,pi]
module file / history_cartesC
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_latxv
latitude at staggered point (xv) [rad,-pi,pi]
integer, dimension(6), public time_nowdate
current time [YYYY MM DD HH MM SS]
Definition: scale_time.F90:69
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazuv_x
virtical area (zuv, normal x) [m2]
module STDIO
Definition: scale_io.F90:10
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazuv_y
virtical area (zuv, normal y) [m2]
subroutine, public prof_rapend(rapname_base, level)
Save raptime.
Definition: scale_prof.F90:210
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cz
center coordinate [m]: z, local
integer, public isga
start point of the full domain: cx, global
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_volzuy
control volume (zuy) [m3]
real(rp), dimension(:,:), allocatable, public landuse_frac_land
land fraction
real(rp), dimension(:,:,:), allocatable, public land_grid_cartesc_real_vol
volume of grid cell
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_areazxv_y
virtical area (zxv, normal y) [m2]
module ocean / grid / cartesianC
module file_history
module file_h
procedure(truncate_3d), pointer, public file_history_truncate_3d
logical, public prc_has_w
subroutine, public file_history_set_nowdate(NOWDATE, NOWMS, NOWSTEP)
set now step
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]