SCALE-RM
Data Types | Functions/Subroutines
scale_file_grads Module Reference

module file_grads More...

Functions/Subroutines

subroutine, public file_grads_open (file_name, file_id)
 Open. More...
 
subroutine, public file_grads_varid (file_id, var_name, var_id)
 
subroutine, public file_grads_varcheck (file_id, var_name, exist)
 
logical function, public file_grads_isoned (file_id, var_id)
 
subroutine file_grads_get_shape_name (file_id, var_name, shape)
 
subroutine file_grads_get_shape_id (file_id, var_id, shape)
 
subroutine file_grads_read_1d_id (file_id, var_id, var, step, start, count, postfix)
 
subroutine file_grads_read_2d_id (file_id, var_id, var, step, start, count, postfix)
 
subroutine file_grads_read_3d_id (file_id, var_id, var, step, start, count, postfix)
 
subroutine, public file_grads_finalize
 
subroutine, public file_grads_close (file_id)
 
subroutine read_data_int1 (fid, pos, ka, nx, k, sx, cx, cy, yrev, var, ierr)
 
character(len=len(str)) function upcase (str)
 

Detailed Description

module file_grads

Description
read data from GrADS file
Author
Team SCALE
NAMELIST
  • GrADS_DIMS
    nametypedefault valuecomment
    NX integer
    NY integer optional
    NZ integer

  • GrADS_ITEM
    nametypedefault valuecomment
    NAME character(len=H_SHORT) up to 16 characters
    DTYPE character(len=H_SHORT) 'linear','levels','map'
    FNAME character(len=H_LONG) head of file name
    SWPOINT real(RP) start point (south-west point) for "linear"
    DD real(RP) dlon,dlat for "linear"
    LNUM integer number of data
    LVARS real(RP), dimension(LVARS_MAX) values for "levels"
    STARTREC integer record position
    TOTALREC integer total record number per one time
    MISSVAL real(SP) missing value
    NX integer
    NY integer optional
    NZ integer
    YREV logical
    BINTYPE character(len=H_SHORT) binary type: 'int?' or 'real?' ?=2,4, or 8

  • nml_grads_grid
    nametypedefault valuecomment
    DUMMY logical

  • grdvar
    nametypedefault valuecomment
    DUMMY logical

History Output
No history output

Function/Subroutine Documentation

◆ file_grads_open()

subroutine, public scale_file_grads::file_grads_open ( character(len=*), intent(in)  file_name,
integer, intent(out)  file_id 
)

Open.

Definition at line 104 of file scale_file_grads.F90.

104  use scale_prc, only: &
105  prc_abort
106  use scale_const, only: &
107  undef => const_undef
108  implicit none
109  character(len=*), intent(in) :: file_name
110  integer, intent(out) :: file_id
111 
112  character(len=H_SHORT) :: name ! up to 16 characters
113  character(len=H_SHORT) :: dtype ! 'linear','levels','map'
114  character(len=H_LONG) :: fname ! head of file name
115  real(RP) :: swpoint ! start point (south-west point) for "linear"
116  real(RP) :: dd ! dlon,dlat for "linear"
117  integer :: lnum ! number of data
118  real(RP) :: lvars(lvars_max) ! values for "levels"
119  integer :: startrec ! record position
120  integer :: totalrec ! total record number per one time
121  real(SP) :: missval ! missing value
122  integer :: nx ! optional
123  integer :: ny ! optional
124  integer :: nz ! optional
125  character(len=H_SHORT) :: fendian ! option for "map"
126  logical :: yrev ! option for "map", if yrev=.true., order of data is NW to SE.
127  character(len=H_SHORT) :: bintype ! binary type: 'int?' or 'real?' ?=2,4, or 8
128 
129  namelist /grads_dims/ &
130  nx, &
131  ny, &
132  nz
133 
134  namelist /grads_item/ &
135  name, & ! necessary
136  dtype, & ! necessary
137  fname, & ! necessary except for linear data
138  swpoint, & ! for linear data
139  dd, & ! for linear data
140  lnum, & ! for levels data
141  lvars, & ! for levels data
142  startrec, & ! for map data
143  totalrec, & ! for map data
144  missval, & ! option
145  nx, & ! option
146  ny, & ! option
147  nz, & ! option
148  yrev, & ! option
149  bintype ! option
150 ! fendian ! option
151 
152  character(len=H_LONG) :: dirname
153 
154  integer :: fid
155  integer :: nvars
156  integer :: ierr
157  integer :: n
158  !---------------------------------------------------------------------------
159 
160  call io_get_fname(fname, file_name)
161 
162  log_newline
163  log_info("FILE_GrADS_open",*) 'open namelist file :', trim(fname)
164 
165  ! check exist
166  do n = 1, nnmls
167  if ( nmls(n)%fname == fname ) then
168  ! alread read
169  file_id = n
170  return
171  end if
172  end do
173 
174 
175  fid = io_get_available_fid()
176  !--- open namelist
177  open( fid, &
178  file = fname, &
179  form = 'formatted', &
180  status = 'old', &
181  action = 'read', &
182  iostat = ierr )
183  if ( ierr /= 0 ) then
184  log_error("FILE_GrADS_open",*) 'Input file is not found! ', trim(fname)
185  call prc_abort
186  endif
187 
188  call check_oldnamelist( fid )
189 
190  !--- read namelist dims
191  read(fid,nml=grads_dims,iostat=ierr)
192  if( ierr /= 0 ) then !--- missing or fatal error
193  log_error("FILE_GrADS_open",*) 'Not appropriate names in GrADS_DIMS in ', trim(fname),'. Check!'
194  call prc_abort
195  endif
196  log_nml(grads_dims)
197 
198 
199  nnmls = nnmls + 1
200  if ( nnmls > nmls_max ) then
201  log_error("FILE_GrADS_open",*) 'Number of GrADS file to be open is exceeded the maximum', nmls_max
202  call prc_abort
203  end if
204  file_id = nnmls
205 
206  nmls(file_id)%fname = file_name
207  nmls(file_id)%nx = nx
208  nmls(file_id)%ny = ny
209  nmls(file_id)%nz = nz
210 
211 
212 
213  !--- count the number of variables
214  rewind(fid)
215  nvars = 0
216  do n = 1, vars_max
217  read(fid, nml=grads_item, iostat=ierr)
218  if( ierr > 0 )then
219  log_error("FILE_GrADS_open",*) 'Not appropriate names in GrADS_ITEM in ', trim(file_name),'. Check!'
220  call prc_abort
221  else if( ierr < 0 )then
222  exit
223  endif
224  nvars = nvars + 1
225  enddo
226 
227  if ( nvars > vars_max ) then
228  log_error("FILE_GRADS_open",*) 'The number of grads vars exceeds the limit! ', &
229  nvars, ' > ', vars_max
230  call prc_abort
231  endif
232 
233  nmls(file_id)%nvars = nvars
234  allocate( nmls(file_id)%vars(nvars) )
235 
236  n = index( file_name, '/', back=.true. )
237  if ( n > 0 ) then
238  dirname = file_name(1:n)
239  else
240  dirname = ""
241  end if
242 
243  !--- read information of the variables
244  rewind(fid)
245  do n = 1, nvars
246 
247  ! set default
248  name = ''
249  dtype = ''
250  fname = ''
251  swpoint = undef
252  dd = undef
253  lnum = -1
254  lvars(:) = undef
255  startrec = -1
256  totalrec = -1
257  nx = nmls(file_id)%nx
258  ny = nmls(file_id)%ny
259  nz = nmls(file_id)%nz
260  yrev = .false.
261  fendian = 'big'
262  missval = undef
263  bintype = 'real4'
264 
265  ! read namelist
266  read(fid, nml=grads_item, iostat=ierr)
267  if( ierr /= 0 ) exit
268 
269  nmls(file_id)%vars(n)%name = upcase(name)
270  if ( fname(1:1) == "/" ) then
271  nmls(file_id)%vars(n)%fname = fname
272  else
273  nmls(file_id)%vars(n)%fname = trim(dirname) // fname
274  end if
275  nmls(file_id)%vars(n)%dtype = dtype
276  nmls(file_id)%vars(n)%swpoint = swpoint
277  nmls(file_id)%vars(n)%dd = dd
278  nmls(file_id)%vars(n)%lnum = lnum
279  if ( lnum > 0 ) then
280  if ( lnum > lvars_max ) then
281  log_error("FILE_GrADS_open",*) 'lnum exceeds the limit', lvars_max
282  call prc_abort
283  end if
284  allocate( nmls(file_id)%vars(n)%lvars(lnum) )
285  nmls(file_id)%vars(n)%lvars(:) = lvars(1:lnum)
286  end if
287  nmls(file_id)%vars(n)%startrec = startrec
288  nmls(file_id)%vars(n)%totalrec = totalrec
289  nmls(file_id)%vars(n)%missval = missval
290  nmls(file_id)%vars(n)%nx = nx
291  nmls(file_id)%vars(n)%ny = ny
292  nmls(file_id)%vars(n)%nz = nz
293  nmls(file_id)%vars(n)%yrev = yrev
294  if ( fendian == "big" ) then
295  nmls(file_id)%vars(n)%endian = 1
296  else
297  nmls(file_id)%vars(n)%endian = 0
298  end if
299  nmls(file_id)%vars(n)%bintype = bintype
300 
301  end do
302 
303  close( fid )
304 

References scale_const::const_undef, scale_io::io_get_available_fid(), scale_io::io_get_fname(), scale_prc::prc_abort(), and upcase().

Referenced by mod_cnv2d::cnv2d_grads_init(), mod_cnvuser::cnvuser(), mod_copytopo::copytopo_get_data_grads(), mod_copytopo::copytopo_get_size_grads(), mod_copytopo::copytopo_get_size_wrfarw(), mod_realinput_grads::parentatmossetupgrads(), mod_realinput_grads::parentlandsetupgrads(), and mod_realinput_grads::parentoceansetupgrads().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_grads_varid()

subroutine, public scale_file_grads::file_grads_varid ( integer, intent(in)  file_id,
character(len=*), intent(in)  var_name,
integer, intent(out)  var_id 
)

Definition at line 312 of file scale_file_grads.F90.

312  use scale_prc, only: &
313  prc_abort
314  implicit none
315  integer, intent(in) :: file_id
316  character(len=*), intent(in) :: var_name
317  integer, intent(out) :: var_id
318 
319  character(len=len(var_name)) :: vname
320  integer :: n
321 
322  if ( file_id < 0 ) then
323  log_error("FILE_GrADS_varid",*) 'file_id is invalid: ', file_id
324  call prc_abort
325  end if
326 
327  vname = upcase(var_name)
328 
329  var_id = -1
330  do n = 1, nmls(file_id)%nvars
331  if ( nmls(file_id)%vars(n)%name == vname ) then
332  var_id = n
333  return
334  end if
335  end do
336 
337  return

References scale_prc::prc_abort(), and upcase().

Referenced by mod_cnv2d::cnv2d_grads_init(), mod_cnvuser::cnvuser(), mod_copytopo::copytopo_get_data_grads(), file_grads_get_shape_id(), file_grads_get_shape_name(), file_grads_read_1d_id(), file_grads_read_2d_id(), file_grads_varcheck(), mod_realinput_grads::parentatmossetupgrads(), mod_realinput_grads::parentlandsetupgrads(), mod_realinput_grads::parentoceaninputgrads(), mod_realinput_grads::parentoceansetupgrads(), mod_realinput_grads::read2d(), and mod_realinput_grads::read3d().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_grads_varcheck()

subroutine, public scale_file_grads::file_grads_varcheck ( integer, intent(in)  file_id,
character(len=*), intent(in)  var_name,
logical, intent(out)  exist 
)

Definition at line 344 of file scale_file_grads.F90.

344  use scale_prc, only: &
345  prc_abort
346  implicit none
347  integer, intent(in) :: file_id
348  character(len=*), intent(in) :: var_name
349  logical, intent(out) :: exist
350 
351  integer :: var_id
352 
353  if ( file_id < 0 ) then
354  log_error("FILE_GrADS_varcheck",*) 'file_id is invalid: ', file_id
355  call prc_abort
356  end if
357 
358  exist = .true.
359 
360  call file_grads_varid( file_id, var_name, & ! (in)
361  var_id ) ! (out)
362  if ( var_id < 0 ) then
363  exist = .false.
364  end if
365 
366  return

References file_grads_varid(), and scale_prc::prc_abort().

Referenced by mod_realinput_grads::parentlandinputgrads().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_grads_isoned()

logical function, public scale_file_grads::file_grads_isoned ( integer, intent(in)  file_id,
integer, intent(in)  var_id 
)

Definition at line 373 of file scale_file_grads.F90.

373  use scale_prc, only: &
374  prc_abort
375  implicit none
376  integer, intent(in) :: file_id
377  integer, intent(in) :: var_id
378  logical :: ret
379 
380  if ( file_id < 0 ) then
381  log_error("FILE_GrADS_isOneD",*) 'file_id is invalid: ', file_id
382  call prc_abort
383  end if
384  if ( var_id < 0 ) then
385  log_error("FILE_GrADS_isOneD",*) 'var_id is invalid: ', var_id
386  call prc_abort
387  end if
388 
389  select case( nmls(file_id)%vars(var_id)%dtype )
390  case ('linear', 'levels')
391  ret = .true.
392  case default
393  ret = .false.
394  end select
395 
396  return

References scale_prc::prc_abort().

Referenced by mod_cnv2d::cnv2d_grads_init(), mod_cnvuser::cnvuser(), mod_copytopo::copytopo_get_data_grads(), file_grads_get_shape_id(), mod_realinput_grads::parentlandsetupgrads(), mod_realinput_grads::parentoceansetupgrads(), mod_realinput_grads::read2d(), and mod_realinput_grads::read3d().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_grads_get_shape_name()

subroutine scale_file_grads::file_grads_get_shape_name ( integer, intent(in)  file_id,
character(len=*), intent(in)  var_name,
integer, dimension(:), intent(out)  shape 
)

Definition at line 404 of file scale_file_grads.F90.

404  use scale_prc, only: &
405  prc_abort
406  implicit none
407  integer, intent(in) :: file_id
408  character(len=*), intent(in) :: var_name
409  integer, intent(out) :: shape(:)
410 
411  integer :: var_id
412 
413  call file_grads_varid( file_id, var_name, & ! (in)
414  var_id ) ! (out)
415 
416  if ( var_id < 0 ) then
417  log_error("FILE_GrADS_get_shape",*) 'variable "', trim(var_name), ' is not founed in file "', trim(nmls(file_id)%fname), '"'
418  call prc_abort
419  end if
420 
421  call file_grads_get_shape_id( file_id, var_id, & ! (in)
422  shape(:) ) ! (out)
423 
424  return

References file_grads_get_shape_id(), file_grads_varid(), and scale_prc::prc_abort().

Here is the call graph for this function:

◆ file_grads_get_shape_id()

subroutine scale_file_grads::file_grads_get_shape_id ( integer, intent(in)  file_id,
integer, intent(in)  var_id,
integer, dimension(:), intent(out)  shape 
)

Definition at line 431 of file scale_file_grads.F90.

431  implicit none
432  integer, intent(in) :: file_id
433  integer, intent(in) :: var_id
434  integer, intent(out) :: shape(:)
435 
436  intrinsic :: size
437 
438  if ( file_grads_isoned( file_id, var_id ) ) then
439  if ( nmls(file_id)%vars(var_id)%dtype == "levels" ) then
440  shape(1) = nmls(file_id)%vars(var_id)%lnum
441  else
442  shape(1) = -1
443  end if
444  else if ( size(shape) == 2 ) then
445  shape(1) = nmls(file_id)%vars(var_id)%nx
446  shape(2) = nmls(file_id)%vars(var_id)%ny
447  else
448  shape(1) = nmls(file_id)%vars(var_id)%nz
449  shape(2) = nmls(file_id)%vars(var_id)%nx
450  shape(3) = nmls(file_id)%vars(var_id)%ny
451  end if
452 
453  return

References file_grads_isoned(), file_grads_read_1d_id(), file_grads_varid(), and scale_prc::prc_abort().

Referenced by file_grads_get_shape_name().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_grads_read_1d_id()

subroutine scale_file_grads::file_grads_read_1d_id ( integer, intent(in)  file_id,
integer, intent(in)  var_id,
real(rp), dimension(:), intent(out)  var,
integer, intent(in), optional  step,
integer, dimension(1), intent(in), optional  start,
integer, dimension(1), intent(in), optional  count,
character(len=*), intent(in), optional  postfix 
)

Definition at line 506 of file scale_file_grads.F90.

506  implicit none
507  integer, intent(in) :: file_id
508  integer, intent(in) :: var_id
509  real(RP), intent(out) :: var(:)
510  integer, intent(in), optional :: step
511  integer, intent(in), optional :: start(1)
512  integer, intent(in), optional :: count(1)
513  character(len=*), intent(in), optional :: postfix
514 
515  logical :: exist
516  integer :: vid
517 
518  intrinsic :: size
519  !---------------------------------------------------------------------------
520 
521  if ( file_id < 0 ) then
522  log_error("FILE_GrADS_read_1D_vid",*) 'file_id is invalid: ', file_id
523  end if
524  if ( var_id < 0 ) then
525  log_error("FILE_GrADS_read_1D_vid",*) 'var_id is invalid: ', var_id
526  end if
527 
528  call file_grads_read_data( nmls(file_id)%vars(var_id), & ! (in)
529  1, size(var), shape(var), & ! (in)
530  var(:), & ! (out)
531  step = step, & ! (int)
532  start = start, & ! (int)
533  count = count, & ! (int)
534  postfix = postfix ) ! (in)
535 
536  return

References file_grads_read_2d_id(), file_grads_varid(), and scale_prc::prc_abort().

Referenced by file_grads_get_shape_id().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_grads_read_2d_id()

subroutine scale_file_grads::file_grads_read_2d_id ( integer, intent(in)  file_id,
integer, intent(in)  var_id,
real(rp), dimension(:,:), intent(out)  var,
integer, intent(in), optional  step,
integer, dimension(2), intent(in), optional  start,
integer, dimension(2), intent(in), optional  count,
character(len=*), intent(in), optional  postfix 
)

Definition at line 588 of file scale_file_grads.F90.

588  implicit none
589  integer, intent(in) :: file_id
590  integer, intent(in) :: var_id
591  real(RP), intent(out) :: var(:,:)
592  integer, intent(in), optional :: step
593  integer, intent(in), optional :: start(2)
594  integer, intent(in), optional :: count(2)
595  character(len=*), intent(in), optional :: postfix
596 
597  integer :: vid
598  intrinsic :: size
599  !---------------------------------------------------------------------------
600 
601  if ( file_id < 0 ) then
602  log_error("FILE_GrADS_read_2D_vid",*) 'file_id is invalid: ', file_id
603  end if
604  if ( var_id < 0 ) then
605  log_error("FILE_GrADS_read_2D_vid",*) 'var_id is invalid: ', var_id
606  end if
607 
608  call file_grads_read_data( nmls(file_id)%vars(var_id), & ! (in)
609  2, size(var), shape(var), & ! (in)
610  var(:,:), & ! (out)
611  step = step, & ! (in)
612  start = start, & ! (in)
613  count = count, & ! (in)
614  postfix = postfix ) ! (in)
615 
616  return

References file_grads_read_3d_id(), file_grads_varid(), and scale_prc::prc_abort().

Referenced by file_grads_read_1d_id().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_grads_read_3d_id()

subroutine scale_file_grads::file_grads_read_3d_id ( integer, intent(in)  file_id,
integer, intent(in)  var_id,
real(rp), dimension(:,:,:), intent(out)  var,
integer, intent(in), optional  step,
integer, dimension(3), intent(in), optional  start,
integer, dimension(3), intent(in), optional  count,
character(len=*), intent(in), optional  postfix 
)

Definition at line 668 of file scale_file_grads.F90.

668  implicit none
669  integer, intent(in) :: file_id
670  integer, intent(in) :: var_id
671  real(RP), intent(out) :: var(:,:,:)
672  integer, intent(in), optional :: step
673  integer, intent(in), optional :: start(3)
674  integer, intent(in), optional :: count(3)
675  character(len=*), intent(in), optional :: postfix
676 
677  integer :: vid
678  intrinsic :: size
679  !---------------------------------------------------------------------------
680 
681  if ( file_id < 0 ) then
682  log_error("FILE_GrADS_read_3D_vid",*) 'file_id is invalid: ', file_id
683  end if
684  if ( var_id < 0 ) then
685  log_error("FILE_GrADS_read_3D_vid",*) 'var_id is invalid: ', var_id
686  end if
687 
688  call file_grads_read_data( nmls(file_id)%vars(var_id), & ! (in)
689  3, size(var), shape(var), & ! (in)
690  var(:,:,:), & ! (out)
691  step = step, & ! (in)
692  start = start, & ! (in)
693  count = count, & ! (in)
694  postfix = postfix ) ! (in)
695 
696  return

Referenced by file_grads_read_2d_id().

Here is the caller graph for this function:

◆ file_grads_finalize()

subroutine, public scale_file_grads::file_grads_finalize

Definition at line 700 of file scale_file_grads.F90.

700  integer :: n
701 
702  do n = 1, nnmls
703  call file_grads_close(n)
704  end do
705  nnmls = 0
706 
707  return

References file_grads_close().

Referenced by mod_rm_driver::rm_driver(), and mod_rm_prep::rm_prep().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_grads_close()

subroutine, public scale_file_grads::file_grads_close ( integer, intent(in)  file_id)

Definition at line 713 of file scale_file_grads.F90.

713  implicit none
714  integer, intent(in) :: file_id
715 
716  integer :: n, m
717 
718  if ( file_id < 0 ) return
719 
720  do n = 1, nmls(file_id)%nvars
721  do m = 1, nfiles
722  if ( files(m)%fname == nmls(file_id)%vars(n)%fname ) then
723  if ( files(m)%fid > 0 ) then
724  close( files(m)%fid )
725  files(m)%fid = -1
726  files(m)%postfix = ""
727  end if
728  exit
729  end if
730  end do
731  if ( nmls(file_id)%vars(n)%lnum > 0 ) deallocate( nmls(file_id)%vars(n)%lvars )
732  nmls(file_id)%vars(n)%lnum = -1
733  end do
734  deallocate( nmls(file_id)%vars )
735  nmls(file_id)%fname = ""
736  nmls(file_id)%nvars = 0
737 
738  return

References scale_const::const_eps, scale_const::const_undef, scale_io::io_get_available_fid(), scale_io::io_get_fname(), scale_prc::prc_abort(), and read_data_int1().

Referenced by mod_copytopo::copytopo_get_data_grads(), and file_grads_finalize().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ read_data_int1()

subroutine scale_file_grads::read_data_int1 ( integer, intent(in)  fid,
integer(8), intent(in)  pos,
integer, intent(in)  ka,
integer, intent(in)  nx,
integer, intent(in)  k,
integer, intent(in)  sx,
integer, intent(in)  cx,
integer, intent(in)  cy,
logical, intent(in)  yrev,
real(rp), dimension(:), intent(out)  var,
integer, intent(out)  ierr 
)

Definition at line 1043 of file scale_file_grads.F90.

1043  integer, intent(in) :: fid
1044  integer(8), intent(in) :: pos
1045  integer, intent(in) :: ka, nx, k, sx, cx, cy
1046  logical, intent(in) :: yrev
1047 
1048  real(RP), intent(out) :: var(:)
1049  integer, intent(out) :: ierr
1050 
1051  integer(1) :: buf(nx,cy)
1052  integer :: i, j
1053 
1054  read(fid, pos=pos, iostat=ierr) buf(:,:)
1055  if ( ierr /= 0 ) return
1056 
1057  if ( yrev ) then
1058  !$omp parallel do
1059  do j = 1, cy
1060  do i = 1, cx
1061  var(k+(i-1)*ka+(j-1)*cx*ka) = buf(sx+i-1,cy-j+1)
1062  end do
1063  end do
1064  else
1065  !$omp parallel do
1066  do j = 1, cy
1067  do i = 1, cx
1068  var(k+(i-1)*ka+(j-1)*cx*ka) = buf(sx+i-1,j)
1069  end do
1070  end do
1071  end if
1072 
1073  return

References scale_prc::prc_abort().

Referenced by file_grads_close().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ upcase()

character(len=len(str)) function scale_file_grads::upcase ( character(len=*), intent(in)  str)

Definition at line 1279 of file scale_file_grads.F90.

1279  character(len=*), intent(in) :: str
1280  character(len=len(str)) :: upcase
1281  integer :: i
1282  do i = 1, len_trim(str)
1283  if ( str(i:i) >= 'a' .and. str(i:i) <= 'z' ) then
1284  upcase(i:i) = char( ichar(str(i:i)) - 32 )
1285  else
1286  upcase(i:i) = str(i:i)
1287  end if
1288  end do
1289  do i = len_trim(str)+1, len(str)
1290  upcase(i:i) = ' '
1291  end do

Referenced by file_grads_open(), and file_grads_varid().

Here is the caller graph for this function:
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:350
scale_atmos_grid_cartesc_index::ka
integer, public ka
Definition: scale_atmos_grid_cartesC_index.F90:47
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_const
module CONSTANT
Definition: scale_const.F90:11
scale_const::const_undef
real(rp), public const_undef
Definition: scale_const.F90:43