SCALE-RM
mod_realinput_nicam.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
14  !-----------------------------------------------------------------------------
15  !
16  !++ used modules
17  !
18  use scale_precision
19  use scale_stdio
20  use scale_tracer
21  use scale_process, only: &
22  myrank => prc_myrank, &
24  use scale_external_io, only: &
25  inicam
26 
27  !-----------------------------------------------------------------------------
28  implicit none
29  private
30  !-----------------------------------------------------------------------------
31  !
32  !++ Public procedure
33  !
34  public :: parentatomsetupnicam
35  public :: parentatomopennicam
36  public :: parentatominputnicam
37  public :: parentlandsetupnicam
38  public :: parentlandinputnicam
39  public :: parentoceansetupnicam
40  public :: parentoceanopennicam
41  public :: parentoceaninputnicam
42 
43  !-----------------------------------------------------------------------------
44  !
45  !++ Public parameters & variables
46  !
47  !-----------------------------------------------------------------------------
48  !
49  !++ Private procedure
50  !
51  !-----------------------------------------------------------------------------
52  !
53  !++ Private parameters & variables
54  !
55  real(RP), parameter :: missval_tg = 50.0_rp
56  real(RP), parameter :: missval_strg = 0.0_rp
57  real(RP), parameter :: missval_sst = 273.1506_rp
58 
59 
60  real(SP), allocatable :: read1DX(:)
61  real(SP), allocatable :: read1DY(:)
62  real(SP), allocatable :: read1DZ(:)
63  real(SP), allocatable :: read3DS(:,:,:,:)
64  real(SP), allocatable :: read4D (:,:,:,:)
65 
66  real(SP), allocatable :: read1DLZ(:)
67  real(SP), allocatable :: read4DL(:,:,:,:)
68 
69  !-----------------------------------------------------------------------------
70 contains
71  !-----------------------------------------------------------------------------
73  subroutine parentatomsetupnicam( &
74  dims, &
75  timelen, &
76  basename_org )
77  use gtool_file, only: &
79  implicit none
80 
81  integer, intent(out) :: dims(6)
82  integer, intent(out) :: timelen
83  character(len=*), intent(in) :: basename_org
84 
85  character(len=H_LONG) :: basename
86  integer :: dims_ncm(4)
87 
88  !---------------------------------------------------------------------------
89 
90  if( io_l ) write(io_fid_log,*) '+++ Real Case/Atom Input File Type: NICAM-NETCDF'
91  basename = "ms_pres"//trim(basename_org)
92  call filegetshape( dims_ncm(:), trim(basename), "ms_pres", 1, single=.true. )
93  timelen = dims_ncm(4)
94 
95  ! full level
96  dims(1) = dims_ncm(3)
97  dims(2) = dims_ncm(1)
98  dims(3) = dims_ncm(2)
99  ! half level
100  ! nicam lat-lon data doesn't have staggered grid system
101  dims(4) = dims(1)
102  dims(5) = dims(2)
103  dims(6) = dims(3)
104 
105  allocate( read1dx( dims(2) ) )
106  allocate( read1dy( dims(3) ) )
107  allocate( read1dz( dims(1) ) )
108  allocate( read3ds( 1, dims(2), dims(3), 1 ) )
109  allocate( read4d( dims(1), dims(2), dims(3), 1 ) )
110 
111  return
112  end subroutine parentatomsetupnicam
113 
114  !-----------------------------------------------------------------------------
115  subroutine parentatomopennicam( &
116  lon_org, &
117  lat_org, &
118  cz_org, &
119  basename_num, &
120  dims )
121  use scale_const, only: &
122  d2r => const_d2r
123  use gtool_file, only: &
124  fileread
125  use scale_external_io, only: &
126  externalfileread
127  implicit none
128 
129  real(RP), intent(out) :: lon_org(:,:)
130  real(RP), intent(out) :: lat_org(:,:)
131  real(RP), intent(out) :: cz_org(:,:,:)
132  character(len=*), intent(in) :: basename_num
133  integer, intent(in) :: dims(6)
134 
135  character(len=H_LONG) :: basename
136 
137  integer :: k, i, j
138 
139  if( io_l ) write(io_fid_log,*) '+++ ScaleLib/IO[realinput]/Categ[AtomOpenNICAM]'
140 
141  basename = "ms_pres"//trim(basename_num)
142  call fileread( read1dx(:), trim(basename), "lon", 1, 1, single=.true. )
143  do j = 1, dims(3)
144  lon_org(:,j) = read1dx(:) * d2r
145  enddo
146 
147  call fileread( read1dy(:), trim(basename), "lat", 1, 1, single=.true. )
148  do i = 1, dims(2)
149  lat_org(i,:) = read1dy(:) * d2r
150  enddo
151 
152  call fileread( read1dz(:), trim(basename), "lev", 1, 1, single=.true. )
153  do j = 1, dims(3)
154  do i = 1, dims(2)
155  cz_org(3:,i,j) = read1dz(:)
156  end do
157  end do
158 
159  call externalfileread( read4d(:,:,:,:), trim(basename), "ms_pres", 1, 1, myrank, inicam, single=.true. )
160  do j = 1, dims(3)
161  do i = 1, dims(2)
162  do k = dims(1)+2, 3, -1
163  ! missing data implies under ground
164  ! For more accurate surface height, we need topograph data
165  ! So surface data is not used at this moment
166  if ( read4d(k-2,i,j,1) <= 0.0_rp ) then
167 ! cz_org(k,i,j) = max( ( cz_org(k+1,i,j) + cz_org(k,i,j) ) * 0.5_RP, 0.0_RP )
168  cz_org(1:k,i,j) = 0.0_rp
169  exit
170  endif
171  enddo
172  enddo
173  enddo
174 
175  return
176  end subroutine parentatomopennicam
177 
178  !-----------------------------------------------------------------------------
179  subroutine parentatominputnicam( &
180  velz_org, &
181  velx_org, &
182  vely_org, &
183  pres_org, &
184  temp_org, &
185  qtrc_org, &
186  basename_num, &
187  dims, &
188  it )
189  use scale_const, only: &
190  rdry => const_rdry, &
191  cpdry => const_cpdry, &
192  p00 => const_pre00, &
193  d2r => const_d2r, &
194  eps => const_eps
195  use scale_external_io, only: &
196  externalfileread, &
197  externalfilereadoffset
198  use scale_atmos_hydrometeor, only: &
199  i_qv
200  implicit none
201 
202  real(RP), intent(out) :: velz_org(:,:,:)
203  real(RP), intent(out) :: velx_org(:,:,:)
204  real(RP), intent(out) :: vely_org(:,:,:)
205  real(RP), intent(out) :: pres_org(:,:,:)
206  real(RP), intent(out) :: temp_org(:,:,:)
207  real(RP), intent(out) :: qtrc_org(:,:,:,:)
208  character(len=*), intent(in) :: basename_num
209  integer, intent(in) :: dims(6)
210  integer, intent(in) :: it
211 
212  real(RP) :: tsfc_org (dims(2),dims(3))
213  real(RP) :: slp_org (dims(2),dims(3))
214  real(RP) :: qvsfc_org(dims(2),dims(3))
215 
216  real(RP) :: pott
217  real(RP) :: rovcp
218  real(RP) :: cpovr
219 
220  integer :: k, i, j
221 
222  character(len=H_LONG) :: basename
223  !---------------------------------------------------------------------------
224 
225  if( io_l ) write(io_fid_log,*) '+++ ScaleLib/IO[realinput]/Categ[AtomInputNICAM]'
226 
228  basename = "ms_u"//trim(basename_num)
229  call externalfilereadoffset( read4d(:,:,:,:), trim(basename), "ms_u", it, it, myrank, inicam, single=.true. )
230  do j = 1, dims(3)
231  do i = 1, dims(2)
232  do k = 1, dims(1)
233  if ( abs(abs(read4d(k,i,j,1))-300.0_sp) < sqrt(eps) ) then ! missing value
234  velx_org(k+2,i,j) = 0.0_rp
235  else
236  velx_org(k+2,i,j) = real( read4D(k,i,j,1), kind=rp )
237  end if
238  end do
239  velx_org(1:2,i,j) = 0.0_rp
240  end do
241  end do
242 
243  basename = "ms_v"//trim(basename_num)
244  call externalfilereadoffset( read4d(:,:,:,:), &
245  trim(basename), &
246  "ms_v", &
247  it, it, &
248  myrank, &
249  inicam, &
250  single=.true. )
251  do j = 1, dims(3)
252  do i = 1, dims(2)
253  do k = 1, dims(1)
254  if ( abs(abs(read4d(k,i,j,1))-300.0_sp) < sqrt(eps) ) then ! missing value
255  vely_org(k+2,i,j) = 0.0_rp
256  else
257  vely_org(k+2,i,j) = real( read4D(k,i,j,1), kind=rp )
258  end if
259  end do
260  vely_org(1:2,i,j) = 0.0_rp
261  end do
262  end do
263 
264  velz_org(:,:,:) = 0.0_rp
265 
266 
267  ! The surface height is not available, so t2 is not used, at this moment.
268 ! basename = "ss_t2m"//trim(basename_num)
269 ! call ExternalFileRead( read3DS(:,:,:,:), trim(basename), "ss_t2m", it, it, myrank, iNICAM, single=.true. )
270 ! tsfc_org(:,:) = real( read3DS(1,:,:,1), kind=RP )
271  basename = "ms_tem"//trim(basename_num)
272  call externalfilereadoffset( read4d(:,:,:,:), trim(basename), "ms_tem", it, it, myrank, inicam, single=.true. )
273  do j = 1, dims(3)
274  do i = 1, dims(2)
275  do k = dims(1), 1, -1
276  if ( read4d(k,i,j,1) <= 50.0_sp ) then ! missing value
277 ! temp_org(k+2,i,j) = tsfc_org(i,j)
278  exit
279  else
280  temp_org(1:k+2,i,j) = real( read4D(k,i,j,1), kind=rp )
281  end if
282 ! if( k==1 ) temp_org(2,i,j) = tsfc_org(i,j) ! no missing value case
283  end do
284  end do
285  end do
286 
287  rovcp = rdry/cpdry
288  cpovr = cpdry/rdry
289 
290  basename = "ss_slp"//trim(basename_num)
291  call externalfilereadoffset( read3ds(:,:,:,:), trim(basename), "ss_slp", it, it, myrank, inicam, single=.true. )
292  slp_org(:,:) = real( read3DS(1,:,:,1), kind=rp )
293  basename = "ms_pres"//trim(basename_num)
294  call externalfileread( read4d(:,:,:,:), trim(basename), "ms_pres", it, it, myrank, inicam, single=.true. )
295  pres_org(3:,:,:) = read4d(:,:,:,1)
296  do j = 1, dims(3)
297  do i = 1, dims(2)
298  do k = dims(1), 1, -1
299  if ( read4d(k,i,j,1) < 0.0_sp ) then ! missing value
300  exit
301  else
302  pres_org(k+2,i,j) = real( read4D(k,i,j,1), kind=rp )
303  end if
304  end do
305  ! If data has missing value, k is the top layer having missing value,
306  ! otherwise k is zero.
307  pott = temp_org(k+3,i,j) * (p00/pres_org(k+3,i,j))**rovcp ! lowest level
308 ! pres_org(k+2,i,j) = P00 * (temp_org(k+2,i,j)/pott)**CPovR ! surface
309  pres_org(1:k+2,i,j) = slp_org(i,j) ! sea level
310  temp_org(1:k+2,i,j) = pott * (slp_org(i,j)/p00)**rovcp ! sea level
311  end do
312  end do
313 
314  basename = "ss_q2m"//trim(basename_num)
315  call externalfileread( read3ds(:,:,:,:), trim(basename), "ss_q2m", it, it, myrank, inicam, single=.true. )
316  qvsfc_org(:,:) = real( read3DS(1,:,:,1), kind=rp )
317  qtrc_org(:,:,:,:) = 0.0_rp
318  basename = "ms_qv"//trim(basename_num)
319  call externalfileread( read4d(:,:,:,:), trim(basename), "ms_qv", it, it, myrank, inicam, single=.true. )
320  do j = 1, dims(3)
321  do i = 1, dims(2)
322  do k = dims(1), 1, -1
323  if ( read4d(k,i,j,1) < 0.0_sp ) then ! missing value
324  qtrc_org(1:k+2,i,j,i_qv) = qvsfc_org(i,j) ! surface and sealevel
325  exit
326  else
327  qtrc_org(k+2,i,j,i_qv) = real( read4D(k,i,j,1), kind=rp )
328  end if
329  end do
330  qtrc_org(1:2,i,j,i_qv) = qvsfc_org(i,j)
331  end do
332  end do
333 
334 
335  return
336  end subroutine parentatominputnicam
337 
338  !-----------------------------------------------------------------------------
340  subroutine parentlandsetupnicam( &
341  ldims, &
342  basename_org )
343  use gtool_file, only: &
345  implicit none
346 
347  integer, intent(out) :: ldims(3)
348  character(len=*), intent(in) :: basename_org
349 
350  character(len=H_LONG) :: basename
351  integer :: dims_ncm(4)
352 
353  !---------------------------------------------------------------------------
354 
355  if( io_l ) write(io_fid_log,*) '+++ Real Case/Land Input File Type: NICAM-NETCDF'
356  basename = "la_tg"//trim(basename_org)
357  call filegetshape( dims_ncm(:), trim(basename), "la_tg", 1, single=.true. )
358  ! land
359  ldims(1) = dims_ncm(3) ! vertical grid of land model
360  ldims(2) = dims_ncm(1)
361  ldims(3) = dims_ncm(2)
362 
363  if ( .not. allocated(read1dx) ) then
364  allocate( read1dx( ldims(2) ) )
365  allocate( read1dy( ldims(3) ) )
366  allocate( read3ds( 1, ldims(2), ldims(3), 1 ) )
367  end if
368 
369  allocate( read1dlz( ldims(1) ) )
370  allocate( read4dl( ldims(1), ldims(2), ldims(3), 1 ) )
371 
372  return
373  end subroutine parentlandsetupnicam
374 
375  !-----------------------------------------------------------------------------
376  subroutine parentlandinputnicam( &
377  tg_org, &
378  strg_org, &
379  lst_org, &
380  llon_org, &
381  llat_org, &
382  lz_org, &
383  topo_org, &
384  lmask_org, &
385  basename_num, &
386  ldims, &
387  use_file_landwater, &
388  it )
389  use scale_const, only: &
390  undef => const_undef, &
391  d2r => const_d2r, &
392  tem00 => const_tem00, &
393  eps => const_eps
394  use gtool_file, only: &
395  fileread
396  use scale_external_io, only: &
397  externalfileread, &
398  externalfilereadoffset
399  implicit none
400 
401  real(RP), intent(out) :: tg_org(:,:,:)
402  real(RP), intent(out) :: strg_org(:,:,:)
403  real(RP), intent(out) :: lst_org(:,:)
404  real(RP), intent(out) :: llon_org(:,:)
405  real(RP), intent(out) :: llat_org(:,:)
406  real(RP), intent(out) :: lz_org(:)
407  real(RP), intent(out) :: topo_org(:,:)
408  real(RP), intent(out) :: lmask_org(:,:)
409  character(len=*), intent(in) :: basename_num
410  integer, intent(in) :: ldims(3)
411  logical, intent(in) :: use_file_landwater ! use land water data from files
412  integer, intent(in) :: it
413 
414  ! work
415  integer :: k, i, j
416 
417  character(len=H_LONG) :: basename
418  !---------------------------------------------------------------------------
419 
420  if( io_l ) write(io_fid_log,*) '+++ ScaleLib/IO[realinput]/Categ[LandInputNICAM]'
421 
422  basename = "la_tg"//trim(basename_num)
423  call fileread( read1dlz(:), trim(basename), "lev", 1, 1, single=.true. )
424  lz_org(:) = read1dlz(:)
425 
426  call fileread( read1dx(:), trim(basename), "lon", 1, 1, single=.true. )
427  do j = 1, ldims(3)
428  llon_org(:,j) = read1dx(:) * d2r
429  enddo
430 
431  call fileread( read1dy(:), trim(basename), "lat", 1, 1, single=.true. )
432  do i = 1, ldims(2)
433  llat_org(i,:) = read1dy(:) * d2r
434  enddo
435 
436  basename = "lsmask"//trim(basename_num)
437  call externalfileread( read3ds(:,:,:,:), &
438  trim(basename), &
439  "lsmask", &
440  it, it, &
441  myrank, &
442  inicam, &
443  single=.true., &
444  option=.true. )
445  lmask_org(:,:) = real( read3DS(1,:,:,1), kind=rp )
446 
447  basename = "la_tg"//trim(basename_num)
448  call externalfilereadoffset( read4dl(:,:,:,:), &
449  trim(basename), &
450  "la_tg", &
451  it, it, &
452  myrank, &
453  inicam, &
454  single=.true. )
455  tg_org(:,:,:) = real( read4DL(:,:,:,1), kind=rp )
456 
457  if( use_file_landwater ) then
458  basename = "la_wg"//trim(basename_num)
459  call externalfilereadoffset( read4dl(:,:,:,:), &
460  trim(basename), &
461  "la_wg", &
462  it, it, &
463  myrank, &
464  inicam, &
465  single=.true. )
466  strg_org(:,:,:) = real( read4DL(:,:,:,1), kind=rp )
467  end if
468 
469  basename = "ss_tem_sfc"//trim(basename_num)
470  call externalfileread( read3ds(:,:,:,:), &
471  trim(basename), &
472  "ss_tem_sfc", &
473  it, it, &
474  myrank, &
475  inicam, &
476  single=.true. )
477  lst_org(:,:) = real( read3DS(1,:,:,1), kind=rp )
478 
479 
480  ! replace missing value
481  do j = 1, ldims(3)
482  do i = 1, ldims(2)
483  do k = 1, ldims(1)
484  if ( abs(tg_org(k,i,j) -missval_tg ) < eps ) tg_org(k,i,j) = undef
485  if ( abs(strg_org(k,i,j)-missval_strg) < eps ) strg_org(k,i,j) = undef
486  end do
487  end do
488  end do
489 
490  topo_org = undef
491 
492  return
493  end subroutine parentlandinputnicam
494 
495  !-----------------------------------------------------------------------------
497  subroutine parentoceansetupnicam( &
498  odims, &
499  timelen, &
500  basename_org )
501  use gtool_file, only: &
503  implicit none
504 
505  integer, intent(out) :: odims(2)
506  integer, intent(out) :: timelen
507  character(len=*), intent(in) :: basename_org
508 
509  character(len=H_LONG) :: basename
510  integer :: dims_ncm(4)
511 
512  !---------------------------------------------------------------------------
513 
514  if( io_l ) write(io_fid_log,*) '+++ Real Case/Ocean Input File Type: NICAM-NETCDF'
515 
516  basename = "oa_sst"//trim(basename_org)
517  call filegetshape( dims_ncm(:), trim(basename), "oa_sst", 1, single=.true. )
518  odims(1) = dims_ncm(1)
519  odims(2) = dims_ncm(2)
520 
521  timelen = dims_ncm(4)
522 
523  if ( .not. allocated(read1dx) ) then
524  allocate( read1dx( odims(1) ) )
525  allocate( read1dy( odims(2) ) )
526  allocate( read3ds( 1, odims(1), odims(2), 1 ) )
527  end if
528 
529  return
530  end subroutine parentoceansetupnicam
531 
532  !-----------------------------------------------------------------------------
533  subroutine parentoceanopennicam( &
534  olon_org, &
535  olat_org, &
536  omask_org, &
537  basename_num, &
538  odims )
539  use scale_const, only: &
540  d2r => const_d2r
541  use gtool_file, only: &
542  fileread
543  use scale_external_io, only: &
544  externalfileread
545  implicit none
546 
547  real(RP), intent(out) :: olon_org(:,:)
548  real(RP), intent(out) :: olat_org(:,:)
549  real(RP), intent(out) :: omask_org(:,:)
550  character(len=*), intent(in) :: basename_num
551  integer, intent(in) :: odims(2)
552 
553  character(len=H_LONG) :: basename
554 
555  integer :: k, i, j
556 
557  if( io_l ) write(io_fid_log,*) '+++ ScaleLib/IO[realinput]/Categ[OceanOpenNICAM]'
558 
559  basename = "oa_sst"//trim(basename_num)
560  call fileread( read1dx(:), trim(basename), "lon", 1, 1, single=.true. )
561  do j = 1, odims(2)
562  olon_org(:,j) = read1dx(:) * d2r
563  enddo
564 
565  call fileread( read1dy(:), trim(basename), "lat", 1, 1, single=.true. )
566  do i = 1, odims(1)
567  olat_org(i,:) = read1dy(:) * d2r
568  enddo
569 
570  basename = "lsmask"//trim(basename_num)
571  call externalfileread( read3ds(:,:,:,:), &
572  trim(basename), &
573  "lsmask", &
574  1, 1, &
575  myrank, &
576  inicam, &
577  single=.true., &
578  option=.true. )
579  omask_org(:,:) = real( read3DS(1,:,:,1), kind=rp )
580 
581  return
582  end subroutine parentoceanopennicam
583 
584  !-----------------------------------------------------------------------------
585  subroutine parentoceaninputnicam( &
586  tw_org, &
587  sst_org, &
588  basename_num, &
589  odims, &
590  omask_org, &
591  it )
592  use scale_const, only: &
593  undef => const_undef, &
594  d2r => const_d2r, &
595  tem00 => const_tem00, &
596  eps => const_eps
597  use gtool_file, only: &
598  fileread
599  use scale_external_io, only: &
600  externalfileread, &
601  externalfilereadoffset
602  implicit none
603 
604  real(RP), intent(out) :: tw_org(:,:)
605  real(RP), intent(out) :: sst_org(:,:)
606  character(len=*), intent(in) :: basename_num
607  integer, intent(in) :: odims(2)
608  real(RP), intent(in) :: omask_org(:,:)
609  integer, intent(in) :: it
610 
611  ! work
612  integer :: i, j
613 
614  character(len=H_LONG) :: basename
615  !---------------------------------------------------------------------------
616 
617  if( io_l ) write(io_fid_log,*) '+++ ScaleLib/IO[realinput]/Categ[OceanInputNICAM]'
618 
619 
620  basename = "oa_sst"//trim(basename_num)
621  call externalfilereadoffset( read3ds(:,:,:,:), &
622  trim(basename), &
623  "oa_sst", &
624  1, 1, &
625  myrank, &
626  inicam, &
627  single=.true. )
628  sst_org(:,:) = real( read3DS(1,:,:,1), kind=rp )
629 
630  !basename = "oa_ice"//trim(basename_num)
631  !call ExternalFileRead( read3DS(:,:,:,:), trim(basename), &
632  ! "oa_ice", 1, 1, myrank, iNICAM, single=.true. )
633  !ice_org(:,:) = real( read3DS(1,:,:,1), kind=RP )
634 
635 
636  ! SST: retrieve SST data around coast
637  do j = 1, odims(2)
638  do i = 1, odims(1)
639  if ( abs(omask_org(i,j)-1.0_rp) < eps ) then ! land data
640  cycle
641  else
642  sst_org(i,j) = ( sst_org(i,j) - missval_sst*omask_org(i,j) ) &
643  / ( 1.0_rp - omask_org(i,j) )
644  end if
645  end do
646  end do
647 
648  tw_org = sst_org
649 
650  return
651  end subroutine parentoceaninputnicam
652 
653 end module mod_realinput_nicam
module GTOOL_FILE
Definition: gtool_file.f90:17
real(rp), public const_cpdry
specific heat (dry air,constant pressure) [J/kg/K]
Definition: scale_const.F90:58
subroutine, public prc_mpistop
Abort MPI.
subroutine, public parentoceanopennicam(olon_org, olat_org, omask_org, basename_num, odims)
subroutine, public parentatomopennicam(lon_org, lat_org, cz_org, basename_num, dims)
subroutine, public parentatominputnicam(velz_org, velx_org, vely_org, pres_org, temp_org, qtrc_org, basename_num, dims, it)
integer, parameter, public inicam
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:61
module STDIO
Definition: scale_stdio.F90:12
real(rp), parameter, public const_tem00
temperature reference (0C) [K]
Definition: scale_const.F90:92
real(rp), public const_d2r
degree to radian
Definition: scale_const.F90:35
module FILE I/O (netcdf)
real(rp), public const_rdry
specific gas constant (dry air) [J/kg/K]
Definition: scale_const.F90:57
real(rp), public const_undef
Definition: scale_const.F90:43
subroutine, public parentoceansetupnicam(odims, timelen, basename_org)
Ocean Setup.
module TRACER
module REAL input NICAM
subroutine, public parentlandinputnicam(tg_org, strg_org, lst_org, llon_org, llat_org, lz_org, topo_org, lmask_org, basename_num, ldims, use_file_landwater, it)
subroutine, public parentatomsetupnicam(dims, timelen, basename_org)
Atmos Setup.
real(rp), public const_pre00
pressure reference [Pa]
Definition: scale_const.F90:90
subroutine, public parentlandsetupnicam(ldims, basename_org)
Land Setup.
module PROCESS
module CONSTANT
Definition: scale_const.F90:14
integer, public prc_myrank
process num in local communicator
real(rp), public const_eps
small number
Definition: scale_const.F90:36
module PRECISION
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
integer, parameter, public rp
subroutine, public parentoceaninputnicam(tw_org, sst_org, basename_num, odims, omask_org, it)
subroutine, public filegetshape(dims, basename, varname, myrank, single, error)