My Project
Data Types | Functions/Subroutines | Variables
mod_station_timeseries Module Reference

Data Types

interface  putvar
 

Functions/Subroutines

subroutine station_name_list_initialize
 
subroutine station_name_list_print
 
subroutine station_name_list_read
 
subroutine read_station_file
 
subroutine out_station_timeseries
 
subroutine write_netcdf_setup
 
subroutine putvar1d_real (i1, i2, n1, n1gl, kt, k1, map_type, var, nc_fid, vid, myid, nprocs, ipt, stk)
 
subroutine putvar2d_real (i1, i2, n1, n1gl, kt, k1, map_type, var, nc_fid, vid, myid, nprocs, ipt, stk)
 
subroutine putvar1d_int (i1, i2, n1, n1gl, kt, k1, map_type, var, nc_fid, vid, myid, nprocs, ipt, stk)
 
subroutine putvar2d_int (i1, i2, n1, n1gl, kt, k1, map_type, var, nc_fid, vid, myid, nprocs, ipt, stk)
 
subroutine putvar_char (i1, i2, var, nc_fid, vid, myid, nprocs, ipt, stk)
 
subroutine triangle_grid_edge_gl
 

Variables

logical out_station_timeseries_on
 
character(len=80) station_file
 
character(len=80) location_type
 
logical out_elevation
 
logical out_velocity_3d
 
logical out_velocity_2d
 
logical out_wind_velocity
 
logical out_salt_temp
 
character(len=80) out_interval
 
integer nsta
 
character(len=20), dimension(:), allocatable name_sta
 
real(sp), dimension(:), allocatable lat_sta
 
real(sp), dimension(:), allocatable lon_sta
 
real(sp), dimension(:), allocatable h_sta
 
integer, dimension(:), allocatable node_sta
 
integer, dimension(:), allocatable element_sta
 
integer, dimension(:), allocatable idummy
 
integer, dimension(:), allocatable ntvegl
 
integer, dimension(:,:), allocatable nbvegl
 
type(time) interval_time_series
 
type(time) time_series
 
integer kd_start
 
type(time) kdd
 
type(time) kdd1
 
character(len=120), public netcdf_timestring
 

Function/Subroutine Documentation

◆ out_station_timeseries()

subroutine mod_station_timeseries::out_station_timeseries ( )

Definition at line 273 of file mod_station_timeseries.f90.

273 
274  USE all_vars
275  USE netcdf
276  use mod_nctools,only : handle_ncerr
277  IMPLICIT NONE
278  REAL(SP), ALLOCATABLE, DIMENSION(:,:) :: UTMP,VTMP,T1TMP,S1TMP
279  REAL(SP), ALLOCATABLE, DIMENSION(:) :: UATMP,VATMP,UUWINDTMP,VVWINDTMP,ELTMP
280  REAL(SP) :: XTT,YTT
281  INTEGER :: I1,I2,J
282 
283  INTEGER ::IZAJ_MAX,IZAJ_MIN,IZAJ,IZAJ_MAX_s,IZAJ_MIN_s,IZAJ_MAX_t,IZAJ_MIN_t
284  INTEGER ::kZAJ_MAX_s,kZAJ_MIN_s,kZAJ_MAX_t,kZAJ_MIN_t
285  INTEGER ::k,ierr
286  REAL(SP) :: THOUR,THOUR1
287  REAL(SP) :: STATMP(NSTA),STATMP1(NSTA),STATMPT(NSTA,KB),STATMPS(NSTA,KB)
288  integer :: dims(1)
289  real(sp), allocatable :: ftemp(:)
290  integer :: VARID
291  REAL(SP) :: KDD_TMP
292 
293 !------------------------------------------------------------------------------!
294 ! WRITE TO FILES (SERIAL EXECUTION) !
295 !------------------------------------------------------------------------------!
296  IF(time_series > inttime) RETURN
297 
299  thour = dti*float(iint-istart+1)/3600.0_sp
300  thour1 = dti*float(iint)/3600.0_sp
301 ! WRITE ELEVATION, SALINITY, TEMPERATURE, VELOCITY AND WIND DATA
302  out_cnt = out_cnt + 1
303  stck_cnt = stck_cnt + 1
304  if(out_cnt == 1) call write_netcdf_setup
305 
306  dims(1) = stck_cnt
307 
308 !--Open File
309  if(msr)then
310  ierr = nf90_open(cdfname,nf90_write,nc_ofid)
311  if(ierr /= nf90_noerr)then
312  call handle_ncerr(ierr,"file open error")
313  end if
314 
315 !--Dump Time/IINT to File
316  ierr = nf90_put_var(nc_ofid,iint_vid,iint,start=dims)
317  if(ierr /= nf90_noerr)then
318  call handle_ncerr(ierr,"error writing variable to netcdf")
319  end if
320 
321  IF(use_real_world_time)THEN
322  kdd1%MJD = kdd%MJD + int((kdd%MuSOD/3600.+thour)/24.0)
323  kdd1%MuSOD = kdd%MuSOD + thour * 3600 - int((kdd%MuSOD/3600.+thour)/24.0) * 24 * 3600
324  kdd_tmp = kdd1%MJD + kdd1%MuSOD/86400.0
325 
326  ierr = nf90_put_var(nc_ofid,time_s_vid,kdd_tmp,start=dims)
327  if(ierr /= nf90_noerr)then
328  call handle_ncerr(ierr,"error writing variable to netcdf")
329  end if
330 
331  ELSE
332  ierr = nf90_put_var(nc_ofid,time_s_vid,thour1*3600.,start=dims)
333  if(ierr /= nf90_noerr)then
334  call handle_ncerr(ierr,"error writing variable to netcdf")
335  end if
336  END IF
337  end if
338 
339 !--Write Variables to File
340  if(msr) write(ipt,*)'dumping to netcdf file: ',trim(cdfname),stck_cnt
341 
342  IF(out_elevation)THEN
343  i1 = lbound(el,1) ; i2 = ubound(el,1)
344  call putvar(i1,i2,m,mgl,1,1,"n",el,nc_ofid,el_s_vid,myid,nprocs&
345  &,ipt, stck_cnt)
346  END IF
347 
348  IF(out_salt_temp)THEN
349  i1 = lbound(t1,1) ; i2 = ubound(t1,1)
350  call putvar(i1,i2,m,mgl,kb,kb-1,"n",t1,nc_ofid,t1_s_vid,myid&
351  &,nprocs,ipt, stck_cnt)
352  i1 = lbound(s1,1) ; i2 = ubound(s1,1)
353  call putvar(i1,i2,m,mgl,kb,kb-1,"n",s1,nc_ofid,s1_s_vid,myid&
354  &,nprocs,ipt, stck_cnt)
355  END IF
356 
357  IF(out_velocity_3d)THEN
358  i1 = lbound(u,1) ; i2 = ubound(u,1)
359  call putvar(i1,i2,n,ngl,kb,kb-1,"e",u,nc_ofid,u_s_vid,myid&
360  &,nprocs,ipt, stck_cnt)
361  i1 = lbound(v,1) ; i2 = ubound(v,1)
362  call putvar(i1,i2,n,ngl,kb,kb-1,"e",v,nc_ofid,v_s_vid,myid&
363  &,nprocs,ipt, stck_cnt)
364  i1 = lbound(ww,1) ; i2 = ubound(ww,1)
365  call putvar(i1,i2,n,ngl,kb,kb-1,"e",ww,nc_ofid,ww_s_vid,myid&
366  &,nprocs,ipt, stck_cnt)
367  END IF
368 
369  IF(out_velocity_2d)THEN
370  allocate(ftemp(n))
371  ftemp =ua(1:n)
372  i1 = lbound(ftemp,1) ; i2 = ubound(ftemp,1)
373  call putvar(i1,i2,n,ngl,1,1,"e",ftemp,nc_ofid,ua_s_vid,myid&
374  &,nprocs,ipt, stck_cnt)
375  deallocate(ftemp)
376  allocate(ftemp(n))
377  ftemp =va(1:n)
378  i1 = lbound(ftemp,1) ; i2 = ubound(ftemp,1)
379  call putvar(i1,i2,n,ngl,1,1,"e",ftemp,nc_ofid,va_s_vid,myid&
380  &,nprocs,ipt, stck_cnt)
381  deallocate(ftemp)
382  END IF
383 
384  IF(out_wind_velocity)THEN
385  allocate(ftemp(n))
386  ftemp =uuwind(1:n)
387  i1 = lbound(ftemp,1) ; i2 = ubound(ftemp,1)
388  call putvar(i1,i2,n,ngl,1,1,"e",ftemp,nc_ofid,uuwind_s_vid,myid&
389  &,nprocs,ipt, stck_cnt)
390  deallocate(ftemp)
391  allocate(ftemp(n))
392  ftemp =vvwind(1:n)
393  i1 = lbound(ftemp,1) ; i2 = ubound(ftemp,1)
394  call putvar(i1,i2,n,ngl,1,1,"e",ftemp,nc_ofid,vvwind_s_vid,myid&
395  &,nprocs,ipt, stck_cnt)
396  deallocate(ftemp)
397  END IF
398 
399 
400 
401  ierr = nf90_close(nc_ofid)
402 
403  RETURN
real(sp), dimension(:), allocatable, target va
Definition: mod_main.f90:1104
logical msr
Definition: mod_main.f90:101
real(sp), dimension(:), allocatable, target el
Definition: mod_main.f90:1134
real(sp), dimension(:,:), allocatable, target v
Definition: mod_main.f90:1269
integer myid
Definition: mod_main.f90:67
subroutine handle_ncerr(status, programer_msg)
real(sp), dimension(:,:), allocatable, target t1
Definition: mod_main.f90:1307
real(sp) dti
Definition: mod_main.f90:844
integer, target nprocs
Definition: mod_main.f90:72
type(time) inttime
Definition: mod_main.f90:827
integer m
Definition: mod_main.f90:56
real(sp), dimension(:,:), allocatable, target ww
Definition: mod_main.f90:1280
integer(itime) istart
Definition: mod_main.f90:852
real(sp), dimension(:,:), allocatable, target u
Definition: mod_main.f90:1268
real(sp), dimension(:,:), allocatable, target s1
Definition: mod_main.f90:1308
integer(itime) iint
Definition: mod_main.f90:850
integer kb
Definition: mod_main.f90:64
integer n
Definition: mod_main.f90:55
integer mgl
Definition: mod_main.f90:50
logical use_real_world_time
Definition: mod_main.f90:131
real(sp), dimension(:), allocatable, target ua
Definition: mod_main.f90:1103
real(sp), dimension(:), allocatable, target vvwind
Definition: mod_main.f90:1233
integer ipt
Definition: mod_main.f90:922
integer ngl
Definition: mod_main.f90:49
real(sp), dimension(:), allocatable, target uuwind
Definition: mod_main.f90:1232
Here is the call graph for this function:
Here is the caller graph for this function:

◆ putvar1d_int()

subroutine mod_station_timeseries::putvar1d_int ( integer, intent(in)  i1,
integer, intent(in)  i2,
integer, intent(in)  n1,
integer, intent(in)  n1gl,
integer, intent(in)  kt,
integer, intent(in)  k1,
character(len=*), intent(in)  map_type,
integer, dimension(i1:i2)  var,
integer, intent(in)  nc_fid,
integer, intent(in)  vid,
integer, intent(in)  myid,
integer, intent(in)  nprocs,
integer, intent(in)  ipt,
integer, intent(in)  stk 
)

Definition at line 825 of file mod_station_timeseries.f90.

825 
826  !------------------------------------------------------------------------------|
827  implicit none
828  integer, intent(in) :: i1,i2,n1,n1gl,kt,k1,nc_fid,vid,myid,nprocs&
829  &,ipt, stk
830  character(len=*),intent(in) :: map_type
831  INTEGER, dimension(i1:i2) :: var
832 
833  INTEGER, allocatable, dimension(:,:) :: temp
834 
835  allocate(temp(i1:i2,kt))
836  temp(i1:i2,kt)= var
837 
838  call putvar2d_int(i1,i2,n1,n1gl,kt,k1,map_type,temp,nc_fid,vid&
839  &,myid,nprocs,ipt, stk)
840 
841  deallocate(temp)
842 
integer myid
Definition: mod_main.f90:67
integer, target nprocs
Definition: mod_main.f90:72
subroutine putvar2d_int(i1, i2, n1, n1gl, kt, k1, map_type, var, nc_fid, vid, myid, nprocs, ipt, stk)
integer nc_fid
integer ipt
Definition: mod_main.f90:922
Here is the call graph for this function:

◆ putvar1d_real()

subroutine mod_station_timeseries::putvar1d_real ( integer, intent(in)  i1,
integer, intent(in)  i2,
integer, intent(in)  n1,
integer, intent(in)  n1gl,
integer, intent(in)  kt,
integer, intent(in)  k1,
character(len=*), intent(in)  map_type,
real(sp), dimension(i1:i2)  var,
integer, intent(in)  nc_fid,
integer, intent(in)  vid,
integer, intent(in)  myid,
integer, intent(in)  nprocs,
integer, intent(in)  ipt,
integer, intent(in)  stk 
)

Definition at line 721 of file mod_station_timeseries.f90.

721 
722  !------------------------------------------------------------------------------|
723  implicit none
724  integer, intent(in) :: i1,i2,n1,n1gl,kt,k1,nc_fid,vid,myid,nprocs&
725  &,ipt,stk
726  character(len=*),intent(in) :: map_type
727  real(sp), dimension(i1:i2) :: var
728 
729  real(sp), allocatable, dimension(:,:) :: temp
730 
731  allocate(temp(i1:i2,kt))
732  temp(i1:i2,1)=var
733 
734  CALL putvar2d_real(i1,i2,n1,n1gl,kt,k1,map_type,temp,nc_fid,vid&
735  &,myid,nprocs,ipt,stk)
736 
737  deallocate(temp)
738 
integer myid
Definition: mod_main.f90:67
integer, target nprocs
Definition: mod_main.f90:72
integer nc_fid
integer ipt
Definition: mod_main.f90:922
subroutine putvar2d_real(i1, i2, n1, n1gl, kt, k1, map_type, var, nc_fid, vid, myid, nprocs, ipt, stk)
Here is the call graph for this function:

◆ putvar2d_int()

subroutine mod_station_timeseries::putvar2d_int ( integer, intent(in)  i1,
integer, intent(in)  i2,
integer, intent(in)  n1,
integer, intent(in)  n1gl,
integer, intent(in)  kt,
integer, intent(in)  k1,
character(len=*), intent(in)  map_type,
integer, dimension(:,:), allocatable  var,
integer, intent(in)  nc_fid,
integer, intent(in)  vid,
integer, intent(in)  myid,
integer, intent(in)  nprocs,
integer, intent(in)  ipt,
integer, intent(in)  stk 
)

Definition at line 847 of file mod_station_timeseries.f90.

847 
848  !------------------------------------------------------------------------------|
849 
850  use all_vars, only : nvg
851  use mod_nctools,only : handle_ncerr
852  use mod_utils, only : pstop
853  implicit none
854  integer, intent(in) :: i1,i2,n1,n1gl,kt,k1,nc_fid,vid,myid,nprocs&
855  &,ipt,stk
856  character(len=*),intent(in) :: map_type
857  INTEGER, allocatable :: var(:,:)
858 
859  INTEGER, allocatable, dimension(:,:) :: temp,gtemp
860  integer :: ierr,k1m1,i,j
861  integer, allocatable :: dims(:)
862 
863 
864  k1m1 = k1
865  if(k1m1 == 1)then
866  allocate(dims(2))
867  dims(1) = 1
868  dims(2) = stk
869  else
870  allocate(dims(3))
871  dims(1) = 1
872  dims(2) = 1
873  dims(3) = stk
874  end if
875 
876 
877  if(map_type(1:1) /= "e" .and. map_type(1:1) /= "n")then
878  write(ipt,*)'map_type input to putvar should be "e" OR "n"'
879  call pstop
880  end if
881 
882  if(nprocs==1)then
883  allocate(temp(nsta,k1m1))
884 
885  if(map_type(1:1) == 'n' .and. trim(location_type) == 'node')then
886  do i=1,nsta
887  temp(i,1:k1m1) = var(node_sta(i),1:k1m1)
888  end do
889  else if(map_type(1:1) == 'e' .and. trim(location_type) == 'cell')then
890  do i=1,nsta
891  temp(i,1:k1m1) = var(element_sta(i),1:k1m1)
892  end do
893  else if(map_type(1:1) == 'n' .and. trim(location_type) == 'cell')then
894  do i=1,nsta
895  temp(i,:) = 0.0_sp
896  do j =1,3
897  temp(i,1:k1m1) = temp(i,1:k1m1) + var(nvg(element_sta(i),j),1:k1m1)
898  end do
899  temp(i,:) = temp(i,:)/3.0_sp
900  end do
901  else if(map_type(1:1) == 'e' .and. trim(location_type) == 'node')then
902  do i=1,nsta
903  temp(i,:) = 0.0_sp
904  do j =1, ntvegl(node_sta(i))
905  temp(i,1:k1m1) = temp(i,1:k1m1) + var(nbvegl(node_sta(i),j),1:k1m1)
906  end do
907  temp(i,:) = temp(i,:)/ntvegl(node_sta(i))
908  end do
909  end if
910  end if
911 
912 
913 ! if(myid /= 1) return
914  if(myid == 1) then
915  ierr = nf90_put_var(nc_fid,vid,temp,start=dims)
916  if(ierr /= nf90_noerr)then
917  call handle_ncerr(ierr,"error writing variable to netcdf")
918  end if
919  end if
920  deallocate(dims,temp)
921 
922  return
integer myid
Definition: mod_main.f90:67
subroutine handle_ncerr(status, programer_msg)
integer, target nprocs
Definition: mod_main.f90:72
integer, dimension(:,:), allocatable nbvegl
subroutine pstop
Definition: mod_utils.f90:273
integer, dimension(:,:), allocatable nvg
Definition: mod_main.f90:969
integer, dimension(:), allocatable ntvegl
integer nc_fid
integer, dimension(:), allocatable node_sta
integer ipt
Definition: mod_main.f90:922
integer, dimension(:), allocatable element_sta
Here is the call graph for this function:
Here is the caller graph for this function:

◆ putvar2d_real()

subroutine mod_station_timeseries::putvar2d_real ( integer, intent(in)  i1,
integer, intent(in)  i2,
integer, intent(in)  n1,
integer, intent(in)  n1gl,
integer, intent(in)  kt,
integer, intent(in)  k1,
character(len=*), intent(in)  map_type,
real(sp), dimension(:,:), allocatable  var,
integer, intent(in)  nc_fid,
integer, intent(in)  vid,
integer, intent(in)  myid,
integer, intent(in)  nprocs,
integer, intent(in)  ipt,
integer, intent(in)  stk 
)

Definition at line 744 of file mod_station_timeseries.f90.

744 !------------------------------------------------------------------------------|
745 
746  use all_vars, only : nvg
747  use mod_nctools,only : handle_ncerr
748  use mod_types
749  use mod_utils, only : pstop
750  implicit none
751  integer, intent(in) :: i1,i2,n1,n1gl,kt,k1,nc_fid,vid,myid,nprocs&
752  &,ipt, stk
753  character(len=*),intent(in) :: map_type
754  real(sp), allocatable :: var(:,:)
755 
756  real(sp), allocatable, dimension(:,:) :: temp,gtemp
757  integer :: ierr,k1m1,i,j
758  integer, allocatable :: dims(:)
759 
760 
761  k1m1 = k1
762  if(k1m1 == 1)then
763  allocate(dims(2))
764  dims(1) = 1
765  dims(2) = stk
766  else
767  allocate(dims(3))
768  dims(1) = 1
769  dims(2) = 1
770  dims(3) = stk
771  end if
772 
773 
774  if(map_type(1:1) /= "e" .and. map_type(1:1) /= "n")then
775  write(ipt,*)'map_type input to putvar should be "e" OR "n"'
776  call pstop
777  end if
778 
779  if(nprocs==1)then
780  allocate(temp(nsta,k1m1))
781 
782  if(map_type(1:1) == 'n' .and. trim(location_type) == 'node')then
783  do i=1,nsta
784  temp(i,1:k1m1) = var(node_sta(i),1:k1m1)
785  end do
786  else if(map_type(1:1) == 'e' .and. trim(location_type) == 'cell')then
787  do i=1,nsta
788  temp(i,1:k1m1) = var(element_sta(i),1:k1m1)
789  end do
790  else if(map_type(1:1) == 'n' .and. trim(location_type) == 'cell')then
791  do i=1,nsta
792  temp(i,:) = 0.0_sp
793  do j =1,3
794  temp(i,1:k1m1) = temp(i,1:k1m1) + var(nvg(element_sta(i),j),1:k1m1)
795  end do
796  temp(i,:) = temp(i,:)/3.0_sp
797  end do
798  else if(map_type(1:1) == 'e' .and. trim(location_type) == 'node')then
799  do i=1,nsta
800  temp(i,:) = 0.0_sp
801  do j =1, ntvegl(node_sta(i))
802  temp(i,1:k1m1) = temp(i,1:k1m1) + var(nbvegl(node_sta(i),j),1:k1m1)
803  end do
804  temp(i,:) = temp(i,:)/ntvegl(node_sta(i))
805  end do
806  end if
807  end if
808 
809 
810 ! if(myid /= 1) return
811  if(myid == 1) then
812  ierr = nf90_put_var(nc_fid,vid,temp,start=dims)
813  if(ierr /= nf90_noerr)then
814  call handle_ncerr(ierr,"error writing variable to netcdf")
815  end if
816  end if
817  deallocate(dims,temp)
818 
819  return
integer myid
Definition: mod_main.f90:67
subroutine handle_ncerr(status, programer_msg)
integer, target nprocs
Definition: mod_main.f90:72
integer, dimension(:,:), allocatable nbvegl
subroutine pstop
Definition: mod_utils.f90:273
integer, dimension(:,:), allocatable nvg
Definition: mod_main.f90:969
integer, dimension(:), allocatable ntvegl
integer nc_fid
integer, dimension(:), allocatable node_sta
integer ipt
Definition: mod_main.f90:922
integer, dimension(:), allocatable element_sta
Here is the call graph for this function:
Here is the caller graph for this function:

◆ putvar_char()

subroutine mod_station_timeseries::putvar_char ( integer, intent(in)  i1,
integer, intent(in)  i2,
character(len=20), dimension(i1:i2)  var,
integer, intent(in)  nc_fid,
integer, intent(in)  vid,
integer, intent(in)  myid,
integer, intent(in)  nprocs,
integer, intent(in)  ipt,
integer, intent(in)  stk 
)

Definition at line 928 of file mod_station_timeseries.f90.

928 
929  !------------------------------------------------------------------------------|
930  use mod_nctools,only : handle_ncerr
931  implicit none
932  integer, intent(in) :: i1,i2,nc_fid,vid,myid,nprocs,ipt, stk
933  CHARACTER(LEN=20), dimension(i1:i2) :: var
934  CHARACTER(LEN=20), allocatable,dimension(:,:) :: var_tmp
935  integer :: ierr
936  integer, allocatable :: dims(:)
937 
938  allocate(dims(2))
939  dims(1) = 1
940  dims(2) = stk
941 
942  allocate(var_tmp(i1:i2,1))
943  var_tmp(i1:i2,1) = var(i1:i2)
944 
945  ierr = nf90_put_var(nc_fid,vid,var_tmp,start=dims)
946  if(ierr /= nf90_noerr)then
947  call handle_ncerr(ierr,"error writing variable to netcdf")
948  end if
949 
950  deallocate(dims)
951 
952  return
subroutine handle_ncerr(status, programer_msg)
integer nc_fid
Here is the call graph for this function:
Here is the caller graph for this function:

◆ read_station_file()

subroutine mod_station_timeseries::read_station_file ( )

Definition at line 165 of file mod_station_timeseries.f90.

166  USE lims, ONLY : mgl,ngl,myid,msrid
167  USE all_vars, ONLY : serial, par, nprocs, h, one_third, nvg,start_date
168  USE mod_utils, ONLY : fatal_error
169  USE mod_utils, ONLY : fopen
170  USE mod_obcs, ONLY : gday1
171 
172  IMPLICIT NONE
173  CHARACTER(LEN=120) :: FNAME
174  CHARACTER(LEN=3) :: NAC
175  INTEGER :: IZAJ_MAX,IOS,IDUMMY1,I
176  LOGICAL :: FEXIST
177 
178  REAL(SP), ALLOCATABLE :: FTEMP(:),FTEMPC(:)
179  INTEGER :: IDD,IMM,IYY,ICC,IHH,IMI,ISS
180  INTEGER :: IDD1,IMM1,IYY1,ICC1,IHH1,IMI1,ISS1
181  INTEGER :: KD_REFERENCE
182 
183  out_cnt = 0
184 
185  ALLOCATE(ftemp(mgl)) ; ftemp = 0.0_sp
186  IF(serial) ftemp = h
187 
188  IF(trim(location_type) == "cell" .OR. trim(location_type) == "CELL")THEN
189  ALLOCATE(ftempc(ngl)) ;ftempc = 0.0_sp
190  DO i = 1,ngl
191  ftempc(i) = one_third*(ftemp(nvg(i,1))+ftemp(nvg(i,2))+ftemp(nvg(i,3)))
192  END DO
193  END IF
194 
195  fname = trim(input_dir)//"/"//trim(station_file)
196  CALL fopen(127,trim(fname),'cfr')
197 
198  IF(msr)THEN
199  izaj_max = 0
200  READ(127,*,iostat=ios)
201  DO WHILE(.true.)
202  READ(127,*,iostat=ios)idummy1
203  IF(ios < 0)EXIT
204  izaj_max = izaj_max + 1
205  END DO
206  nsta=izaj_max
207  print *,'NSTA=',nsta
208  ALLOCATE(name_sta(nsta))
209  ALLOCATE(lat_sta(nsta))
210  ALLOCATE(lon_sta(nsta))
211  ALLOCATE(h_sta(nsta))
212  ALLOCATE(idummy(nsta))
213  IF(trim(location_type) == 'node' .OR. trim(location_type) == 'NODE')THEN
214  ALLOCATE(node_sta(nsta))
215  ELSE IF(trim(location_type) == 'cell' .OR. trim(location_type) == 'CELL')THEN
216  ALLOCATE(element_sta(nsta))
217  ELSE
218  CALL fatal_error("LOCATION_TYPE should be either node or cell")
219  END IF
220  rewind(127)
221 
222  READ(127,*)
223  DO i=1,nsta
224  IF(trim(location_type) == "node" .OR. trim(location_type) == "NODE")THEN
225  READ(127,*)idummy(i),lon_sta(i),lat_sta(i),node_sta(i),h_sta(i),name_sta(i)
226  WRITE(6,*) idummy(i),lon_sta(i),lat_sta(i),node_sta(i),h_sta(i),ftemp(node_sta(i)),name_sta(i)
227  ELSE IF(trim(location_type) == "cell" .OR. trim(location_type) == "CELL")THEN
228  READ(127,*)idummy(i),lon_sta(i),lat_sta(i),element_sta(i),h_sta(i),name_sta(i)
229  WRITE(6,*) idummy(i),lon_sta(i),lat_sta(i),element_sta(i),h_sta(i),ftempc(element_sta(i)),name_sta(i)
230  END IF
231  ENDDO
232  CLOSE(127)
233 
234  END IF
235 
236  DEALLOCATE(ftemp)
237  IF(trim(location_type) == "cell" .OR. trim(location_type) == "CELL")DEALLOCATE(ftempc)
238 
239  IF(use_real_world_time)THEN
240  READ(start_date(1:2),*) icc
241  READ(start_date(3:4),*) iyy
242  READ(start_date(6:7),*) imm
243  READ(start_date(9:10),*) idd
244  READ(start_date(12:13),*) ihh
245  READ(start_date(15:16),*) imi
246  READ(start_date(18:19),*) iss
247 
248  CALL gday1(idd,imm,iyy,icc,kd_start)
249 
250  IF(date_reference /= 'default')THEN
251  READ(date_reference(1:2),*) icc1
252  READ(date_reference(3:4),*) iyy1
253  READ(date_reference(6:7),*) imm1
254  READ(date_reference(9:10),*) idd1
255  READ(date_reference(12:13),*) ihh1
256  READ(date_reference(15:16),*) imi1
257  READ(date_reference(18:19),*) iss1
258 
259  CALL gday1(idd1,imm1,iyy1,icc1,kd_reference)
260  ELSE
261  CALL gday1(17,11,58,18,kd_reference)
262  END IF
263 
264  kd_start = kd_start - kd_reference
265  kdd%MJD = kd_start
266  kdd%MuSOD = ihh*3600.+imi*60.+iss
267  END IF
268 
269  RETURN
character(len=80) casename
Definition: mod_main.f90:116
logical msr
Definition: mod_main.f90:101
real(sp), dimension(:), allocatable, target h
Definition: mod_main.f90:1131
character(len=20), dimension(:), allocatable name_sta
real(sp), dimension(:), allocatable h_sta
real(sp), dimension(:), allocatable lat_sta
integer myid
Definition: mod_main.f90:67
character(len=80) output_dir
Definition: mod_main.f90:184
real(sp), dimension(:), allocatable lon_sta
character(len=80) date_reference
Definition: mod_main.f90:129
integer, dimension(:), allocatable idummy
subroutine gday1(IDD, IMM, IYY, ICC, KD)
Definition: mod_obcs.f90:1023
integer, dimension(:,:), allocatable nvg
Definition: mod_main.f90:969
subroutine fopen(IUNIT, INSTR, IOPT)
Definition: mod_utils.f90:1577
integer mgl
Definition: mod_main.f90:50
logical use_real_world_time
Definition: mod_main.f90:131
subroutine fatal_error(ER1, ER2, ER3, ER4)
Definition: mod_utils.f90:230
integer, dimension(:), allocatable node_sta
character(len=80) input_dir
Definition: mod_main.f90:183
integer msrid
Definition: mod_main.f90:68
integer ios
Definition: mod_obcs2.f90:81
integer ngl
Definition: mod_main.f90:49
integer, dimension(:), allocatable element_sta
Here is the call graph for this function:
Here is the caller graph for this function:

◆ station_name_list_initialize()

subroutine mod_station_timeseries::station_name_list_initialize ( )

Definition at line 101 of file mod_station_timeseries.f90.

101 
102  IMPLICIT NONE
103 
104  out_station_timeseries_on = .false.
105  station_file = "'none'"
106  location_type = "'node' or 'cell'"
107  out_elevation = .false.
108  out_velocity_3d = .false.
109  out_velocity_2d = .false.
110  out_wind_velocity = .false.
111  out_salt_temp = .false.
112  out_interval = "A length of time: 'seconds= ','days= ', or 'cycles= '"
113 
114 
115  RETURN
Here is the caller graph for this function:

◆ station_name_list_print()

subroutine mod_station_timeseries::station_name_list_print ( )

Definition at line 119 of file mod_station_timeseries.f90.

119  USE control, ONLY : ipt
120 
121  IMPLICIT NONE
122 
123  WRITE(unit=ipt,nml=nml_station_timeseries)
124 
125  RETURN
integer ipt
Definition: mod_main.f90:922
Here is the caller graph for this function:

◆ station_name_list_read()

subroutine mod_station_timeseries::station_name_list_read ( )

Definition at line 129 of file mod_station_timeseries.f90.

129  USE control, ONLY : casename,nmlunit
130  USE mod_utils
132 
133  IMPLICIT NONE
134 
135  INTEGER :: IOS, I
136  CHARACTER(LEN=120) :: FNAME
137  CHARACTER(LEN=160) :: PATHNFILE
138 
139  IF(dbg_set(dbg_sbr)) &
140  & WRITE(ipt,*) "Subroutine Begins: Read_Station_Name_List;"
141 
142  ios = 0
143 
144  fname = "./"//trim(casename)//"_run.nml"
145 
146  CALL fopen(nmlunit,trim(fname),'cfr')
147 
148  !READ NAME LIST FILE
149  rewind(nmlunit)
150 
151  ! Read IO Information
152  READ(unit=nmlunit, nml=nml_station_timeseries,iostat=ios)
153  if(ios .NE. 0 ) Then
154  if(dbg_set(dbg_log)) write(unit=ipt,nml=nml_station_timeseries)
155  Call fatal_error("Can Not Read NameList NML_STATION_TIMESERIES from file: "//trim(fname))
156  end if
157  CLOSE(nmlunit)
158 
159 ! CALL GET_OUTPUT_FILE_INTERVAL(TRIM(OUT_INTERVAL),INTERVAL_TIME_SERIES)
160 
161  RETURN
character(len=80) casename
Definition: mod_main.f90:116
subroutine get_output_file_interval(STRING, INTERVAL)
integer, parameter nmlunit
Definition: mod_main.f90:926
logical function dbg_set(vrb)
Definition: mod_utils.f90:182
subroutine fopen(IUNIT, INSTR, IOPT)
Definition: mod_utils.f90:1577
subroutine fatal_error(ER1, ER2, ER3, ER4)
Definition: mod_utils.f90:230
integer, parameter dbg_sbr
Definition: mod_utils.f90:69
integer ios
Definition: mod_obcs2.f90:81
integer, parameter dbg_log
Definition: mod_utils.f90:65
Here is the call graph for this function:
Here is the caller graph for this function:

◆ triangle_grid_edge_gl()

subroutine mod_station_timeseries::triangle_grid_edge_gl ( )

Definition at line 957 of file mod_station_timeseries.f90.

957 
958 !==============================================================================|
959 ! DEFINE NTVEGL, NBVEGL !
960 ! !
961 ! ntvegl(1:mgl): total number of the surrounding triangles !
962 ! connected to the given node !
963 ! nbvegl(1:mgl, 1:ntvegl+1): the identification number of surrounding !
964 ! triangles with a common node (counted clockwise) !
965 !==============================================================================|
966  USE all_vars
967  IMPLICIT NONE
968  INTEGER I,J,NCNT,MX_NBR_ELEM_GL
969 
970 !
971 !----DETERMINE MAX NUMBER OF SURROUNDING ELEMENTS------------------------------!
972 !
973  mx_nbr_elem_gl = 0
974  DO i=1,mgl
975  ncnt = 0
976  DO j=1,ngl
977  IF( float(nvg(j,1)-i)*float(nvg(j,2)-i)*float(nvg(j,3)-i) == 0.0_sp) &
978  ncnt = ncnt + 1
979  END DO
980  mx_nbr_elem_gl = max(mx_nbr_elem_gl,ncnt)
981  END DO
982 
983 !
984 !----ALLOCATE ARRAYS BASED ON MX_NBR_ELEM--------------------------------------!
985 !
986  ALLOCATE(ntvegl(mgl)); ntvegl = 0
987  ALLOCATE(nbvegl(mgl,mx_nbr_elem_gl+1)); nbvegl = 0
988 !
989 !--DETERMINE NUMBER OF SURROUNDING ELEMENTS FOR NODE I = NTVEGL(I)---------------!
990 !--DETERMINE NBVEGL - INDICES OF NEIGHBORING ELEMENTS OF NODE I------------------!
991 !
992 
993  DO i=1,mgl
994  ncnt=0
995  DO j=1,ngl
996  IF (float(nvg(j,1)-i)*float(nvg(j,2)-i)*float(nvg(j,3)-i) == 0.0_sp)THEN
997  ncnt = ncnt+1
998  nbvegl(i,ncnt)=j
999  END IF
1000  ENDDO
1001  ntvegl(i)=ncnt
1002  ENDDO
1003 
1004  RETURN
integer, dimension(:,:), allocatable nbvegl
integer, dimension(:,:), allocatable nvg
Definition: mod_main.f90:969
integer, dimension(:), allocatable ntvegl
integer mgl
Definition: mod_main.f90:50
integer ngl
Definition: mod_main.f90:49
Here is the caller graph for this function:

◆ write_netcdf_setup()

subroutine mod_station_timeseries::write_netcdf_setup ( )

Definition at line 411 of file mod_station_timeseries.f90.

411 
412  use all_vars
413  use mod_clock
414  use mod_nctools
415 
416  use netcdf
417  use mod_types
418  use mod_utils
419  implicit none
420  integer, dimension(3) :: dynm2de_lay,dynm2dn_lay
421  integer, dimension(2) :: dynm2ds
422  integer, dimension(1) :: stat2ds
423  integer, dimension(2) :: stat2ds_lev,stat2ds_lay
424  integer, dimension(2) :: stat2ds_char
425  integer, dimension(1) :: dynmtime
426  character(len=100) :: netcdf_convention
427  character(len=100) :: timestamp ,temp
428  integer :: i,j,ierr,i1,i2
429 
430 !==============================================================================|
431 
432 !==============================================================================|
433 ! Set up Constants and Initialize Counters |
434 !==============================================================================|
435 netcdf_timestring = 'seconds after 00:00:00'
436 !--Initialize Stack Count
437  stck_cnt = 1
438 
439 !--NetCDF Convention String
440  netcdf_convention = 'CF-1.0'
441 
442 !--Time Stamp for History
443  call get_timestamp(temp)
444  timestamp = 'model started at: '//trim(temp)
445 
446 
447 !==============================================================================|
448 ! OPEN FILE AND DEFINE VARIABLES |
449 !==============================================================================|
450  if(msr)then
451 
452  cdfname = trim(output_dir)//trim(casename)//'_station_timeseries.nc'
453 
454 !--Create File
455  ierr = nf90_create(path=cdfname,cmode=nf90_clobber,ncid=nc_ofid)
456  if(ierr /= nf90_noerr)then
457  call handle_ncerr(ierr,"file creation error")
458  end if
459 
460 !--Description of File Contents
461  ierr = nf90_put_att(nc_ofid,nf90_global,"title" ,trim(case_title))
462  ierr = nf90_put_att(nc_ofid,nf90_global,"institution",trim(institution))
463  ierr = nf90_put_att(nc_ofid,nf90_global,"source" ,trim(fvcom_version))
464  ierr = nf90_put_att(nc_ofid,nf90_global,"history" ,trim(timestamp))
465  ierr = nf90_put_att(nc_ofid,nf90_global,"references" ,trim(fvcom_website))
466  ierr = nf90_put_att(nc_ofid,nf90_global,"Conventions",trim(netcdf_convention))
467 
468 !--Define Fixed Model Dimensions
469  ierr = nf90_def_dim(nc_ofid,"siglay" ,kbm1 ,siglay_did )
470  ierr = nf90_def_dim(nc_ofid,"siglev" ,kb ,siglev_did )
471  ierr = nf90_def_dim(nc_ofid,"station" ,nsta ,station_did )
472  ierr = nf90_def_dim(nc_ofid,"clen", 20, clen_did )
473 
474 !--Define Unlimited Model Dimension
475  ierr = nf90_def_dim(nc_ofid,"time" ,nf90_unlimited,time_did)
476 
477 !--Set Up Data Dimensioning - Static Vars
478  stat2ds = (/station_did/) !!2d station vars
479  stat2ds_lev = (/station_did,siglev_did/)
480  stat2ds_lay = (/station_did,siglay_did/)
481  stat2ds_char = (/clen_did,station_did/)
482 
483 !--Set Up Data Dimensioning - Dynamic Vars
484  dynm2ds = (/station_did,time_did/) !!2d station vars
485  dynm2de_lay = (/station_did,siglay_did,time_did/)
486  dynm2dn_lay = (/station_did,siglay_did,time_did/)
487  dynmtime = (/time_did/)
488 
489 !--Define Station Name Variables and Attributes
490 
491  !!====Station Name (NAME_STA) ===================!
492  ierr = nf90_def_var(nc_ofid,"name_station",nf90_char,stat2ds_char,name_s_vid)
493  ierr = nf90_put_att(nc_ofid,name_s_vid,"long_name","Station Name")
494 
495 !--Define Coordinate Variables and Attributes
496  !!====X Grid Coordinate at Nodes (VX) (Meters)===========!
497  ierr = nf90_def_var(nc_ofid,"x",nf90_float,stat2ds,x_s_vid)
498  ierr = nf90_put_att(nc_ofid,x_s_vid,"long_name","station x-coordinate")
499  ierr = nf90_put_att(nc_ofid,x_s_vid,"units","meters")
500 
501  !!====Y Grid Coordinate at Nodes (VY) (Meters)===========!
502  ierr = nf90_def_var(nc_ofid,"y",nf90_float,stat2ds,y_s_vid)
503  ierr = nf90_put_att(nc_ofid,y_s_vid,"long_name","station y-coordinate")
504  ierr = nf90_put_att(nc_ofid,y_s_vid,"units","meters")
505 
506  !!====Longitudinal Coordinate at Nodes (LON) (degrees)===!
507  ierr = nf90_def_var(nc_ofid,"lon",nf90_float,stat2ds,lon_s_vid)
508  ierr = nf90_put_att(nc_ofid,lon_s_vid,"long_name","Longitude")
509  ierr = nf90_put_att(nc_ofid,lon_s_vid,"standard_name","longitude")
510  ierr = nf90_put_att(nc_ofid,lon_s_vid,"units","degrees_east")
511 
512  !!====Latitudinal Coordinate at Nodes (LAT) (degrees)===!
513  ierr = nf90_def_var(nc_ofid,"lat",nf90_float,stat2ds,lat_s_vid)
514  ierr = nf90_put_att(nc_ofid,lat_s_vid,"long_name","Latitude")
515  ierr = nf90_put_att(nc_ofid,lat_s_vid,"standard_name","latitude")
516  ierr = nf90_put_att(nc_ofid,lat_s_vid,"units","degrees_north")
517  ierr = nf90_put_att(nc_ofid,lat_s_vid,"grid","Bathymetry_Mesh")
518 
519  !!====Sigma Coordinate for Sigma Layers (ZZ) (-)========!
520  ierr = nf90_def_var(nc_ofid,"siglay",nf90_float,stat2ds_lay,siglay_vid)
521  ierr = nf90_put_att(nc_ofid,siglay_vid,"long_name","Sigma Layers")
522  ierr = nf90_put_att(nc_ofid,siglay_vid,"standard_name","ocean_sigma/general_coordinate")
523  ierr = nf90_put_att(nc_ofid,siglay_vid,"positive","up")
524  ierr = nf90_put_att(nc_ofid,siglay_vid,"valid_min","-1")
525  ierr = nf90_put_att(nc_ofid,siglay_vid,"valid_max","0")
526  ierr = nf90_put_att(nc_ofid,siglay_vid,"formula_terms","siglay:siglay eta:zeta depth:depth")
527 
528  !!====Sigma Coordinate for Sigma Levels (Z) (-)========!
529  ierr = nf90_def_var(nc_ofid,"siglev",nf90_float,stat2ds_lev,siglev_vid)
530  ierr = nf90_put_att(nc_ofid,siglev_vid,"long_name","Sigma Levels")
531  ierr = nf90_put_att(nc_ofid,siglev_vid,"standard_name","ocean_sigma/general_coordinate")
532  ierr = nf90_put_att(nc_ofid,siglev_vid,"positive","up")
533  ierr = nf90_put_att(nc_ofid,siglev_vid,"valid_min","-1")
534  ierr = nf90_put_att(nc_ofid,siglev_vid,"valid_max","0")
535  ierr = nf90_put_att(nc_ofid,siglev_vid,"formula_terms","siglev:siglev eta:zeta depth:depth")
536 
537 !--Define Mesh Relevant Variables and Attributes
538 
539  !!====Bathymetry at Nodes (H) (meters)===================!
540  ierr = nf90_def_var(nc_ofid,"h",nf90_float,stat2ds,h_s_vid)
541  ierr = nf90_put_att(nc_ofid,h_s_vid,"long_name","Bathymetry")
542  ierr = nf90_put_att(nc_ofid,h_s_vid,"units","meters")
543  ierr = nf90_put_att(nc_ofid,h_s_vid,"positive","down")
544  ierr = nf90_put_att(nc_ofid,h_s_vid,"standard_name","depth")
545 
546 !--Define Model Time Variables and Attributes
547  IF(use_real_world_time)THEN
548  ierr = nf90_def_var(nc_ofid,"time",nf90_float,dynmtime,time_s_vid)
549  ierr = nf90_put_att(nc_ofid,time_s_vid,"long_name","time")
550  if(date_reference == 'default')then
551  ierr = nf90_put_att(nc_ofid,time_s_vid,"units",trim("days since 1858-11-17 00:00:00"))
552  ierr = nf90_put_att(nc_ofid,time_s_vid,"format",trim("modified julian day (MJD)"))
553  else
554  ierr = nf90_put_att(nc_ofid,time_s_vid,"units","days since "//trim(date_reference))
555  ierr = nf90_put_att(nc_ofid,time_s_vid,"format",trim("defined reference date"))
556  end if
557 !JQI ierr = nf90_put_att(nc_ofid,time_s_vid,"calendar","none")
558  ierr = nf90_put_att(nc_ofid,time_s_vid,"time_zone","UTC")
559 
560  ELSE
561  ierr = nf90_def_var(nc_ofid,"time",nf90_float,dynmtime,time_s_vid)
562  ierr = nf90_put_att(nc_ofid,time_s_vid,"long_name","time")
563  ierr = nf90_put_att(nc_ofid,time_s_vid,"units",trim(netcdf_timestring))
564 !JQI ierr = nf90_put_att(nc_ofid,time_s_vid,"calendar","none")
565  ierr = nf90_put_att(nc_ofid,time_s_vid,"time_zone","none")
566  END IF
567 
568  ierr = nf90_def_var(nc_ofid,"iint",nf90_int,dynmtime,iint_vid)
569  ierr = nf90_put_att(nc_ofid,iint_vid,"long_name","internal mode iteration number")
570 
571 !--Define Time Dependent Flow Variables (selected by user from input file)
572  if(out_velocity_3d)then
573  ierr = nf90_def_var(nc_ofid,"u",nf90_float,dynm2de_lay,u_s_vid)
574  ierr = nf90_put_att(nc_ofid,u_s_vid,"long_name","Eastward Water Velocity")
575  ierr = nf90_put_att(nc_ofid,u_s_vid,"standard_name","eastward_sea_water_velocity")
576  ierr = nf90_put_att(nc_ofid,u_s_vid,"units","meters s-1")
577  ierr = nf90_put_att(nc_ofid,u_s_vid,"type","data")
578  ierr = nf90_put_att(nc_ofid,u_s_vid,"coordinates","time siglay station")
579 
580  ierr = nf90_def_var(nc_ofid,"v",nf90_float,dynm2de_lay,v_s_vid)
581  ierr = nf90_put_att(nc_ofid,v_s_vid,"long_name","Northward Water Velocity")
582  ierr = nf90_put_att(nc_ofid,u_s_vid,"standard_name","northward_sea_water_velocity")
583  ierr = nf90_put_att(nc_ofid,v_s_vid,"units","meters s-1")
584  ierr = nf90_put_att(nc_ofid,v_s_vid,"type","data")
585  ierr = nf90_put_att(nc_ofid,v_s_vid,"coordinates","time siglay station")
586 
587  ierr = nf90_def_var(nc_ofid,"ww",nf90_float,dynm2de_lay,ww_s_vid)
588  ierr = nf90_put_att(nc_ofid,ww_s_vid,"long_name","Upward Water Velocity")
589  ierr = nf90_put_att(nc_ofid,ww_s_vid,"units","meters s-1")
590  ierr = nf90_put_att(nc_ofid,ww_s_vid,"type","data")
591  end if
592 
593  if(out_velocity_2d)then
594  ierr = nf90_def_var(nc_ofid,"ua",nf90_float,dynm2ds,ua_s_vid)
595  ierr = nf90_put_att(nc_ofid,ua_s_vid,"long_name","Vertically Averaged x-velocity")
596  ierr = nf90_put_att(nc_ofid,ua_s_vid,"units","meters s-1")
597  ierr = nf90_put_att(nc_ofid,ua_s_vid,"type","data")
598 
599  ierr = nf90_def_var(nc_ofid,"va",nf90_float,dynm2ds,va_s_vid)
600  ierr = nf90_put_att(nc_ofid,va_s_vid,"long_name","Vertically Averaged y-velocity")
601  ierr = nf90_put_att(nc_ofid,va_s_vid,"units","meters s-1")
602  ierr = nf90_put_att(nc_ofid,va_s_vid,"type","data")
603  end if
604 
605  if(out_salt_temp)then
606  ierr = nf90_def_var(nc_ofid,"temp",nf90_float,dynm2dn_lay,t1_s_vid)
607  ierr = nf90_put_att(nc_ofid,t1_s_vid,"long_name","temperature")
608  ierr = nf90_put_att(nc_ofid,t1_s_vid,"standard_name","sea_water_temperature")
609  ierr = nf90_put_att(nc_ofid,t1_s_vid,"units","degrees_C")
610  ierr = nf90_put_att(nc_ofid,t1_s_vid,"type","data")
611  ierr = nf90_put_att(nc_ofid,t1_s_vid,"coordinates","time siglay station")
612 
613  ierr = nf90_def_var(nc_ofid,"salinity",nf90_float,dynm2dn_lay,s1_s_vid)
614  ierr = nf90_put_att(nc_ofid,s1_s_vid,"long_name","salinity")
615  ierr = nf90_put_att(nc_ofid,s1_s_vid,"standard_name","sea_water_salinity")
616  ierr = nf90_put_att(nc_ofid,s1_s_vid,"units","1e-3")
617  ierr = nf90_put_att(nc_ofid,s1_s_vid,"type","data")
618  ierr = nf90_put_att(nc_ofid,s1_s_vid,"coordinates","time siglay station")
619  end if
620 
621  if(out_elevation)then
622  ierr = nf90_def_var(nc_ofid,"zeta",nf90_float,dynm2ds,el_s_vid)
623  ierr = nf90_put_att(nc_ofid,el_s_vid,"long_name","Water Surface Elevation")
624  ierr = nf90_put_att(nc_ofid,el_s_vid,"units","meters")
625  ierr = nf90_put_att(nc_ofid,el_s_vid,"positive","up")
626  ierr = nf90_put_att(nc_ofid,el_s_vid,"standard_name","sea_surface_height_above_geoid")
627  ierr = nf90_put_att(nc_ofid,el_s_vid,"type","data")
628  ierr = nf90_put_att(nc_ofid,el_s_vid,"coordinates","time station")
629  end if
630 
631  if(out_wind_velocity)then
632  ierr = nf90_def_var(nc_ofid,"uwind_speed",nf90_float,dynm2ds,uuwind_s_vid)
633  ierr = nf90_put_att(nc_ofid,uuwind_s_vid,"long_name","Eastward wind velocity")
634  ierr = nf90_put_att(nc_ofid,uuwind_s_vid,"units","(m/s)")
635  ierr = nf90_put_att(nc_ofid,uuwind_s_vid,"standard_name","eastward wind")
636  ierr = nf90_put_att(nc_ofid,uuwind_s_vid,"type","data")
637  ierr = nf90_put_att(nc_ofid,uuwind_s_vid,"coordinates","time station")
638 
639  ierr = nf90_def_var(nc_ofid,"vwind_speed",nf90_float,dynm2ds,vvwind_s_vid)
640  ierr = nf90_put_att(nc_ofid,vvwind_s_vid,"long_name","Northward wind velocity")
641  ierr = nf90_put_att(nc_ofid,vvwind_s_vid,"units","(m/s)")
642  ierr = nf90_put_att(nc_ofid,vvwind_s_vid,"standard_name","northward wind")
643  ierr = nf90_put_att(nc_ofid,vvwind_s_vid,"type","data")
644  ierr = nf90_put_att(nc_ofid,vvwind_s_vid,"coordinates","time station")
645  end if
646 
647 
648 !--Exit Define Mode
649  ierr = nf90_enddef(nc_ofid)
650  ierr = nf90_close(nc_ofid)
651 
652  end if !(msr)
653 
654 !==============================================================================|
655 ! WRITE VARIABLES TO FILE |
656 !==============================================================================|
657  if(msr)then
658  ierr = nf90_open(cdfname,nf90_write,nc_ofid)
659  if(ierr /= nf90_noerr)then
660  call handle_ncerr(ierr,"file open error")
661  end if
662  end if
663 
664  !!====Longitude at Nodes (LON) ==========================!
665  i1 = lbound(lon,1) ; i2 = ubound(lon,1)
666  call putvar(i1,i2,m,mgl,1,1,"n",lon,nc_ofid,lon_s_vid,myid&
667  &,nprocs,ipt, stck_cnt)
668 
669  !!====Latitude at Nodes (LAT) ==========================!
670  i1 = lbound(lat,1) ; i2 = ubound(lat,1)
671  call putvar(i1,i2,m,mgl,1,1,"n",lat,nc_ofid,lat_s_vid,myid&
672  &,nprocs,ipt, stck_cnt)
673 
674  !!====X Grid Coordinate at Nodes (VX)====================!
675  i1 = lbound(vx,1) ; i2 = ubound(vx,1)
676  call putvar(i1,i2,m,mgl,1,1,"n",vx+vxmin,nc_ofid,x_s_vid,myid,nprocs&
677  &,ipt, stck_cnt)
678 
679  !!====Y Grid Coordinate at Nodes (VY)====================!
680  i1 = lbound(vy,1) ; i2 = ubound(vy,1)
681  call putvar(i1,i2,m,mgl,1,1,"n",vy+vymin,nc_ofid,y_s_vid,myid,nprocs&
682  &,ipt, stck_cnt)
683 
684  !!====Bathymetry at Nodes (H)============================!
685  i1 = lbound(h,1) ; i2 = ubound(h,1)
686  call putvar(i1,i2,m,mgl,1,1,"n",h,nc_ofid,h_s_vid,myid,nprocs,ipt,&
687  & stck_cnt)
688 
689  !!====Sigma Layers (zz)==================================!
690  i1 = lbound(zz,1) ; i2 = ubound(zz,1)
691  call putvar(i1,i2,m,mgl,kb,kb-1,"n",zz,nc_ofid,siglay_vid,myid&
692  &,nprocs,ipt, stck_cnt)
693 
694  !!====Sigma Levels (z)==================================!
695  i1 = lbound(z,1) ; i2 = ubound(z,1)
696  call putvar(i1,i2,m,mgl,kb,kb,"n",z,nc_ofid,siglev_vid,myid,nprocs&
697  &,ipt, stck_cnt)
698 
699  !!====Station Name (NAME_STA)============================!
700  if(msr)then
701  i1 = lbound(name_sta,1) ; i2 = ubound(name_sta,1)
702  call putvar_char(i1,i2,name_sta,nc_ofid,name_s_vid,myid,nprocs,ipt,&
703  & stck_cnt)
704  end if
705 
706 !==============================================================================|
707 ! close the file |
708 !==============================================================================|
709 
710  if(msr) ierr = nf90_close(nc_ofid)
711 
712  return
character(len=80) casename
Definition: mod_main.f90:116
subroutine get_timestamp(TS)
Definition: mod_clock.f90:322
real(sp), dimension(:), allocatable, target h
Definition: mod_main.f90:1131
character(len=20), dimension(:), allocatable name_sta
character(len=120), public netcdf_timestring
integer myid
Definition: mod_main.f90:67
subroutine handle_ncerr(status, programer_msg)
real(sp) vymin
Definition: mod_main.f90:989
real(sp), dimension(:), allocatable, target vx
Definition: mod_main.f90:1001
real(sp), dimension(:), allocatable, target vy
Definition: mod_main.f90:1002
integer mgl
Definition: mod_main.f90:50
real(sp), dimension(:), allocatable, target lat
Definition: mod_main.f90:996
real(sp), dimension(:,:), allocatable, target z
Definition: mod_main.f90:1090
real(sp), dimension(:), allocatable, target lon
Definition: mod_main.f90:995
subroutine putvar_char(i1, i2, var, nc_fid, vid, myid, nprocs, ipt, stk)
real(sp), dimension(:,:), allocatable, target zz
Definition: mod_main.f90:1091
real(sp) vxmin
Definition: mod_main.f90:989
Here is the call graph for this function:
Here is the caller graph for this function:

Variable Documentation

◆ element_sta

integer, dimension(:), allocatable mod_station_timeseries::element_sta

Definition at line 44 of file mod_station_timeseries.f90.

◆ h_sta

real(sp), dimension(:), allocatable mod_station_timeseries::h_sta

Definition at line 43 of file mod_station_timeseries.f90.

◆ idummy

integer, dimension(:), allocatable mod_station_timeseries::idummy

Definition at line 44 of file mod_station_timeseries.f90.

◆ interval_time_series

type(time) mod_station_timeseries::interval_time_series

Definition at line 47 of file mod_station_timeseries.f90.

47  TYPE(TIME) :: INTERVAL_TIME_SERIES, TIME_SERIES

◆ kd_start

integer mod_station_timeseries::kd_start

Definition at line 48 of file mod_station_timeseries.f90.

48  INTEGER :: KD_START

◆ kdd

type(time) mod_station_timeseries::kdd

Definition at line 49 of file mod_station_timeseries.f90.

49  TYPE(TIME) :: KDD,KDD1

◆ kdd1

type(time) mod_station_timeseries::kdd1

Definition at line 49 of file mod_station_timeseries.f90.

◆ lat_sta

real(sp), dimension(:), allocatable mod_station_timeseries::lat_sta

Definition at line 43 of file mod_station_timeseries.f90.

43  REAL(SP), ALLOCATABLE :: LAT_STA(:),LON_STA(:),H_STA(:)

◆ location_type

character(len=80) mod_station_timeseries::location_type

Definition at line 22 of file mod_station_timeseries.f90.

22  CHARACTER(LEN=80) LOCATION_TYPE

◆ lon_sta

real(sp), dimension(:), allocatable mod_station_timeseries::lon_sta

Definition at line 43 of file mod_station_timeseries.f90.

◆ name_sta

character(len=20), dimension(:), allocatable mod_station_timeseries::name_sta

Definition at line 42 of file mod_station_timeseries.f90.

42  CHARACTER(LEN=20), ALLOCATABLE :: NAME_STA(:)

◆ nbvegl

integer, dimension(:,:), allocatable mod_station_timeseries::nbvegl

Definition at line 45 of file mod_station_timeseries.f90.

◆ netcdf_timestring

character(len=120), public mod_station_timeseries::netcdf_timestring

Definition at line 88 of file mod_station_timeseries.f90.

88  character(len=120),public :: netcdf_timestring

◆ node_sta

integer, dimension(:), allocatable mod_station_timeseries::node_sta

Definition at line 44 of file mod_station_timeseries.f90.

44  INTEGER, ALLOCATABLE :: NODE_STA(:),ELEMENT_STA(:),IDUMMY(:)

◆ nsta

integer mod_station_timeseries::nsta

Definition at line 41 of file mod_station_timeseries.f90.

41  INTEGER NSTA

◆ ntvegl

integer, dimension(:), allocatable mod_station_timeseries::ntvegl

Definition at line 45 of file mod_station_timeseries.f90.

45  INTEGER, ALLOCATABLE :: NTVEGL(:),NBVEGL(:,:)

◆ out_elevation

logical mod_station_timeseries::out_elevation

Definition at line 23 of file mod_station_timeseries.f90.

23  LOGICAL OUT_ELEVATION

◆ out_interval

character(len=80) mod_station_timeseries::out_interval

Definition at line 28 of file mod_station_timeseries.f90.

28  CHARACTER(LEN=80) OUT_INTERVAL

◆ out_salt_temp

logical mod_station_timeseries::out_salt_temp

Definition at line 27 of file mod_station_timeseries.f90.

27  LOGICAL OUT_SALT_TEMP

◆ out_station_timeseries_on

logical mod_station_timeseries::out_station_timeseries_on

Definition at line 20 of file mod_station_timeseries.f90.

20  LOGICAL OUT_STATION_TIMESERIES_ON

◆ out_velocity_2d

logical mod_station_timeseries::out_velocity_2d

Definition at line 25 of file mod_station_timeseries.f90.

25  LOGICAL OUT_VELOCITY_2D

◆ out_velocity_3d

logical mod_station_timeseries::out_velocity_3d

Definition at line 24 of file mod_station_timeseries.f90.

24  LOGICAL OUT_VELOCITY_3D

◆ out_wind_velocity

logical mod_station_timeseries::out_wind_velocity

Definition at line 26 of file mod_station_timeseries.f90.

26  LOGICAL OUT_WIND_VELOCITY

◆ station_file

character(len=80) mod_station_timeseries::station_file

Definition at line 21 of file mod_station_timeseries.f90.

21  CHARACTER(LEN=80) STATION_FILE

◆ time_series

type(time) mod_station_timeseries::time_series

Definition at line 47 of file mod_station_timeseries.f90.