13 use missing_values_mod
15 use fckit_mpi_module,
only: fckit_mpi_comm, fckit_mpi_sum
41 real(kind_real),
allocatable :: vals(:,:)
55 character(len=MAXVARLEN),
allocatable :: variables(:)
57 real(c_double) :: missing_value
59 logical :: linit = .false.
72 self%missing_value = missing_value(0.0)
83 use oops_variables_mod
86 type(oops_variables),
intent(in) :: vars
87 integer,
intent(in) :: nlocs, nvars
88 integer(c_size_t),
intent(in) :: nvals(nvars)
94 self%missing_value = missing_value(self%missing_value)
96 self%nvar = vars%nvars()
97 allocate(self%geovals(self%nvar))
98 allocate(self%variables(self%nvar))
99 do ivar = 1, self%nvar
100 self%variables(ivar) = vars%variable(ivar)
101 self%geovals(ivar)%nlocs = nlocs
102 self%geovals(ivar)%nval = nvals(ivar)
103 allocate(self%geovals(ivar)%vals(nvals(ivar), nlocs))
104 self%geovals(ivar)%vals(:,:) = 0.0
115 use oops_variables_mod
118 type(oops_variables),
intent(in) :: vars
119 integer,
intent(in) :: nlocs
125 self%missing_value = missing_value(self%missing_value)
127 self%nvar = vars%nvars()
128 allocate(self%geovals(self%nvar))
129 allocate(self%variables(self%nvar))
130 do ivar = 1, self%nvar
131 self%variables(ivar) = vars%variable(ivar)
132 self%geovals(ivar)%nlocs = nlocs
133 self%geovals(ivar)%nval = 0
144 use oops_variables_mod
147 type(oops_variables),
intent(in) :: vars
148 integer,
intent(in) :: nlevels
150 integer :: ivar, ivar_gvals
151 character(max_string) :: err_msg
153 do ivar = 1, vars%nvars()
157 if (ivar_gvals < 0)
then
158 write(err_msg,*)
"ufo_geovals_allocate: ", trim(vars%variable(ivar)),
" doesn't exist in geovals"
159 call abor1_ftn(err_msg)
162 if (
allocated(self%geovals(ivar_gvals)%vals) .and. (self%geovals(ivar_gvals)%nval /= nlevels))
then
163 write(err_msg,*)
"ufo_geovals_allocate: attempting to allocate already allocated geovals for ", &
164 trim(vars%variable(ivar)),
". Previously allocated as ", self%geovals(ivar_gvals)%nval, &
165 " levels; now trying to allocate as ", nlevels,
" levels."
166 call abor1_ftn(err_msg)
168 elseif (.not.
allocated(self%geovals(ivar_gvals)%vals))
then
169 self%geovals(ivar_gvals)%nval = nlevels
170 allocate(self%geovals(ivar_gvals)%vals(nlevels, self%nlocs))
176 do ivar = 1, self%nvar
177 if (.not.
allocated(self%geovals(ivar)%vals)) self%linit = .false.
190 if (
allocated(self%geovals))
then
191 do ivar = 1, self%nvar
192 if (
allocated(self%geovals(ivar)%vals))
deallocate(self%geovals(ivar)%vals)
194 deallocate(self%geovals)
196 if (
allocated(self%variables))
deallocate(self%variables)
208 character(len=*),
intent(in) :: varname
209 type(
ufo_geoval),
pointer,
intent(inout) :: geoval
211 character(len=*),
parameter :: myname_=
"ufo_geovals_get_var"
213 character(max_string) :: err_msg
217 if (.not. self%linit)
then
224 write(0,*)
'ufo_geovals_get_var looking for ',trim(varname),
' in:'
226 write(0,*)
'ufo_geovals_get_var ',jv,trim(self%variables(jv))
228 write(err_msg,*) myname_,
" ", trim(varname),
' doesnt exist'
229 call abor1_ftn(err_msg)
231 geoval => self%geovals(ivar)
243 if (.not. self%linit)
then
244 call abor1_ftn(
"ufo_geovals_zero: geovals not initialized")
246 do ivar = 1, self%nvar
247 self%geovals(ivar)%vals(:,:) = 0.0
259 if (.not. self%linit)
then
260 call abor1_ftn(
"ufo_geovals_abs: geovals not initialized")
262 do ivar = 1, self%nvar
263 self%geovals(ivar)%vals = abs(self%geovals(ivar)%vals)
273 real(kind_real),
intent(inout) :: vrms
277 if (.not. self%linit)
then
278 call abor1_ftn(
"ufo_geovals_rms: geovals not initialized")
283 do jo = 1, self%nlocs
284 vrms = vrms + sum(self%geovals(jv)%vals(:,jo)**2)
285 n=n+self%geovals(jv)%nval
289 if ( n > 0) vrms = sqrt(vrms/n)
302 if (.not. self%linit)
then
303 call abor1_ftn(
"ufo_geovals_random: geovals not initialized")
305 do ivar = 1, self%nvar
306 call normal_distribution(self%geovals(ivar)%vals, 0.0_kind_real, 1.0_kind_real, rseed)
316 real(kind_real),
intent(in) :: zz
317 integer :: jv, jo, jz
319 if (.not. self%linit)
then
320 call abor1_ftn(
"ufo_geovals_scalmult: geovals not allocated")
325 do jz = 1, self%geovals(jv)%nval
326 self%geovals(jv)%vals(jz,jo) = zz * self%geovals(jv)%vals(jz,jo)
338 integer(c_int),
intent(in) :: nlocs
339 real(c_float),
intent(in) :: values(nlocs)
342 if (.not. self%linit)
then
343 call abor1_ftn(
"ufo_geovals_profmult: geovals not allocated")
348 self%geovals(jv)%vals(:,jo) = values(jo) * self%geovals(jv)%vals(:,jo)
361 integer :: jv, jo, jz
363 character(max_string) :: err_msg
365 if (.not. self%linit)
then
366 call abor1_ftn(
"ufo_geovals_scalmult: geovals not allocated")
368 if (.not. rhs%linit)
then
369 call abor1_ftn(
"ufo_geovals_scalmult: geovals not allocated")
372 if (self%nlocs /= rhs%nlocs)
then
373 call abor1_ftn(
"ufo_geovals_assign: nlocs different between lhs and rhs")
379 write(err_msg,*)
'ufo_geovals_assign: var ', trim(self%variables(jv)),
' doesnt exist in rhs'
380 call abor1_ftn(trim(err_msg))
382 if (self%geovals(jv)%nval /= rhs%geovals(iv)%nval)
then
383 write(err_msg,*)
'ufo_geovals_assign: nvals for var ', trim(self%variables(jv)),
' are different in lhs and rhs'
384 call abor1_ftn(trim(err_msg))
387 do jz = 1, self%geovals(jv)%nval
388 self%geovals(jv)%vals(jz,jo) = rhs%geovals(iv)%vals(jz,jo)
399 character(len=*),
intent(in) :: varname
400 character(len=*),
intent(in) :: zdir
404 character(max_string) :: err_msg
405 integer:: iobs, ivar, ival, kval
410 if (.not. self%linit)
then
411 call abor1_ftn(
"ufo_geovals_reorderzdir: geovals not allocated")
416 if (.not.
associated(geoval))
then
417 write(err_msg, *)
'ufo_geovals_reorderzdir: geoval vertical coordinate variable ', trim(varname),
' doesnt exist'
421 if ((zdir ==
"bottom2top" .and. geoval%vals(1,1) < geoval%vals(geoval%nval,1)) .or. &
422 (zdir ==
"top2bottom" .and. geoval%vals(1,1) > geoval%vals(geoval%nval,1)))
then
424 else if (zdir /=
"bottom2top" .or. zdir /=
"top2bottom")
then
425 write(err_msg, *)
'ufo_geovals_reorderzdir: z-coordinate direction ', trim(zdir),
' not defined'
433 do ivar = 1, self%nvar
434 do ival = 1, self%geovals(ivar)%nval
435 kval = self%geovals(ivar)%nval - ival + 1
436 self%geovals(ivar)%vals(ival,:) = selfclone%geovals(ivar)%vals(kval,:)
452 integer :: jv, jo, jz
454 character(max_string) :: err_msg
456 if (.not. self%linit)
then
457 call abor1_ftn(
"ufo_geovals_add: geovals not allocated")
459 if (.not. other%linit)
then
460 call abor1_ftn(
"ufo_geovals_add: geovals not allocated")
463 if (self%nlocs /= other%nlocs)
then
464 call abor1_ftn(
"ufo_geovals_add: nlocs different between lhs and rhs")
470 if (self%geovals(jv)%nval /= other%geovals(iv)%nval)
then
471 write(err_msg,*)
'ufo_geovals_add: nvals for var ', trim(self%variables(jv)),
' are different in lhs and rhs'
472 call abor1_ftn(trim(err_msg))
475 do jz = 1, self%geovals(jv)%nval
476 self%geovals(jv)%vals(jz,jo) = self%geovals(jv)%vals(jz,jo) + other%geovals(iv)%vals(jz,jo)
491 integer :: jv, jo, jz
493 character(max_string) :: err_msg
495 if (.not. self%linit)
then
496 call abor1_ftn(
"ufo_geovals_diff: geovals not allocated")
498 if (.not. other%linit)
then
499 call abor1_ftn(
"ufo_geovals_diff: geovals not allocated")
502 if (self%nlocs /= other%nlocs)
then
503 call abor1_ftn(
"ufo_geovals_diff: nlocs different between lhs and rhs")
509 if (self%geovals(jv)%nval /= other%geovals(iv)%nval)
then
510 write(err_msg,*)
'ufo_geovals_diff: nvals for var ', trim(self%variables(jv)),
' are different in lhs and rhs'
511 call abor1_ftn(trim(err_msg))
514 do jz = 1, self%geovals(jv)%nval
515 self%geovals(jv)%vals(jz,jo) = self%geovals(jv)%vals(jz,jo) - other%geovals(iv)%vals(jz,jo)
530 integer :: jv, jo, jz
532 character(max_string) :: err_msg
534 if (.not. self%linit)
then
535 call abor1_ftn(
"ufo_geovals_schurmult: geovals not allocated")
537 if (.not. other%linit)
then
538 call abor1_ftn(
"ufo_geovals_schurmult: geovals not allocated")
541 if (self%nlocs /= other%nlocs)
then
542 call abor1_ftn(
"ufo_geovals_schurmult: nlocs different between lhs and rhs")
548 if (self%geovals(jv)%nval /= other%geovals(iv)%nval)
then
549 write(err_msg,*)
'ufo_geovals_schurmult: nvals for var ', trim(self%variables(jv)),
' are different in lhs and rhs'
550 call abor1_ftn(trim(err_msg))
553 do jz = 1, self%geovals(jv)%nval
554 self%geovals(jv)%vals(jz,jo) = self%geovals(jv)%vals(jz,jo) * other%geovals(iv)%vals(jz,jo)
572 if (.not. self%linit)
then
573 call abor1_ftn(
"ufo_geovals_copy: geovals not defined")
578 other%nlocs = self%nlocs
579 other%nvar = self%nvar
580 allocate(other%variables(other%nvar))
581 other%variables(:) = self%variables(:)
583 allocate(other%geovals(other%nvar))
584 do jv = 1, other%nvar
585 other%geovals(jv)%nval = self%geovals(jv)%nval
586 other%geovals(jv)%nlocs = self%geovals(jv)%nlocs
587 allocate(other%geovals(jv)%vals(other%geovals(jv)%nval, other%geovals(jv)%nlocs))
588 other%geovals(jv)%vals(:,:) = self%geovals(jv)%vals(:,:)
591 other%missing_value = self%missing_value
604 integer,
intent(in) :: loc_index
607 if (.not. other%linit)
then
608 call abor1_ftn(
"ufo_geovals_copy_one: geovals not defined")
614 self%nvar = other%nvar
615 allocate(self%variables(self%nvar))
616 self%variables(:) = other%variables(:)
618 allocate(self%geovals(self%nvar))
620 self%geovals(jv)%nval = other%geovals(jv)%nval
621 self%geovals(jv)%nlocs = 1
622 allocate(self%geovals(jv)%vals(self%geovals(jv)%nval, self%geovals(jv)%nlocs))
623 self%geovals(jv)%vals(:,self%nlocs) = other%geovals(jv)%vals(:,loc_index)
626 self%missing_value = other%missing_value
660 use dcmip_initial_conditions_test_1_2_3,
only : test1_advection_deformation, &
661 test1_advection_hadley, test3_gravity_wave
662 use dcmip_initial_conditions_test_4,
only : test4_baroclinic_wave
669 character(*),
intent(in) :: ic
671 real(kind_real) :: pi = acos(-1.0_kind_real)
672 real(kind_real) :: deg_to_rad,rlat, rlon
673 real(kind_real) :: p0, kz, u0, v0, w0, t0, phis0, ps0, rho0, hum0
674 real(kind_real) :: q1, q2, q3, q4
675 real(kind_real),
allocatable,
dimension(:) :: lons, lats
676 integer ::
nlocs, ivar, iloc, ival
678 if (.not. self%linit)
then
679 call abor1_ftn(
"ufo_geovals_analytic_init: geovals not defined")
684 if (self%variables(self%nvar) /=
var_prs .and. &
685 self%variables(self%nvar) /=
var_prsi)
then
686 call abor1_ftn(
"ufo_geovals_analytic_init: pressure coordinate not defined")
689 deg_to_rad = pi/180.0_kind_real
693 call locs%get_lons(lons)
694 call locs%get_lats(lats)
696 do ivar = 1, self%nvar-1
698 do iloc = 1, self%geovals(ivar)%nlocs
701 rlat = deg_to_rad * lats(iloc)
702 rlon = deg_to_rad*modulo(lons(iloc)+180.0_kind_real,360.0_kind_real) - pi
704 do ival = 1, self%geovals(ivar)%nval
709 p0 = self%geovals(self%nvar)%vals(ival,iloc)
711 init_option:
select case (trim(ic))
713 case (
"invent_state")
715 t0 = cos(deg_to_rad * lons(iloc) ) * cos(rlat)
717 case (
"dcmip-test-1-1")
719 call test1_advection_deformation(rlon,rlat,p0,kz,0,u0,v0,w0,&
720 t0,phis0,ps0,rho0,hum0,q1,q2,q3,q4)
722 case (
"dcmip-test-1-2")
724 call test1_advection_hadley(rlon,rlat,p0,kz,0,u0,v0,w0,&
725 t0,phis0,ps0,rho0,hum0,q1)
727 case (
"dcmip-test-3-1")
729 call test3_gravity_wave(rlon,rlat,p0,kz,0,u0,v0,w0,&
730 t0,phis0,ps0,rho0,hum0)
732 case (
"dcmip-test-4-0")
734 call test4_baroclinic_wave(0,1.0_kind_real,rlon,rlat,p0,kz,0,u0,v0,w0,&
735 t0,phis0,ps0,rho0,hum0,q1,q2)
739 call abor1_ftn(
"ufo_geovals_analytic_init: invalid analytic_init")
741 end select init_option
747 self%geovals(ivar)%vals(ival,iloc) = t0
754 deallocate(lons, lats)
778 integer :: jv, jo, jz
779 real(kind_real) :: over_nloc, vrms, norm
781 if (.not. self%linit)
then
782 call abor1_ftn(
"ufo_geovals_normalize: geovals not allocated")
784 if (.not. other%linit)
then
785 call abor1_ftn(
"ufo_geovals_normalize: geovals not allocated")
787 if (self%nvar /= other%nvar)
then
788 call abor1_ftn(
"ufo_geovals_normalize: reference geovals object must have the same variables as the original")
798 over_nloc = 1.0_kind_real / &
799 (real(other%nlocs,kind_real)*real(other%geovals(jv)%nval,kind_real))
802 do jo = 1, other%nlocs
803 do jz = 1, other%geovals(jv)%nval
804 vrms = vrms + other%geovals(jv)%vals(jz,jo)**2
808 if (vrms > 0.0_kind_real)
then
809 norm = 1.0_kind_real / sqrt(vrms*over_nloc)
816 do jz = 1, self%geovals(jv)%nval
817 self%geovals(jv)%vals(jz,jo) = norm*self%geovals(jv)%vals(jz,jo)
830 integer,
intent(in) :: nlocs
833 if (other%linit)
call abor1_ftn(
"ufo_geovals_reset_sec_arg: other already have data")
836 other%nvar = self%nvar
837 other%missing_value = self%missing_value
838 allocate(other%variables(self%nvar))
839 allocate(other%geovals(self%nvar))
840 do ivar = 1, self%nvar
841 other%variables(ivar) = self%variables(ivar)
842 other%geovals(ivar)%nlocs = nlocs
843 other%geovals(ivar)%nval = self%geovals(ivar)%nval
844 allocate(other%geovals(ivar)%vals(self%geovals(ivar)%nval, nlocs))
845 other%geovals(ivar)%vals(:,:) = 0.0
847 other%linit = .false.
858 integer :: ivar, iobs
860 if (.not. self%linit) &
861 call abor1_ftn(
"ufo_geovals_split: geovals self is not allocated or has no data")
863 if (other1%linit .or. other2%linit) &
864 call abor1_ftn(
"ufo_geovals_split: geovals other1 or other2 already have data")
871 do ivar = 1, self%nvar
872 do iobs = 1, self%nlocs/2
873 other1%geovals(ivar)%vals(:,iobs) = self%geovals(ivar)%vals(:,iobs)
875 do iobs = self%nlocs/2 + 1, self%nlocs
876 other2%geovals(ivar)%vals(:,iobs - self%nlocs/2) = self%geovals(ivar)%vals(:,iobs)
879 other1%linit = .true.
880 other2%linit = .true.
891 integer :: ivar, iobs
893 if ((.not. other1%linit) .or. (.not. other2%linit)) &
894 call abor1_ftn(
"ufo_geovals_merge: geovals other1 or other2 is not allocated or has no data")
899 do ivar = 1, self%nvar
900 do iobs = 1, other1%nlocs
901 self%geovals(ivar)%vals(:,iobs) = other1%geovals(ivar)%vals(:,iobs)
903 do iobs = other1%nlocs + 1, self%nlocs
904 self%geovals(ivar)%vals(:,iobs) = &
905 other2%geovals(ivar)%vals(:,iobs - other1%nlocs)
915 integer,
intent(inout) :: kobs
916 integer,
intent(in) :: kvar
917 real(kind_real),
intent(inout) :: pmin, pmax, prms
919 integer :: jo, jz, jv
926 do jo = 1, self%nlocs
927 do jz = 1, self%geovals(jv)%nval
928 if (self%geovals(jv)%vals(jz,jo) .ne. self%missing_value)
then
930 if (self%geovals(jv)%vals(jz,jo) < pmin) pmin = self%geovals(jv)%vals(jz,jo)
931 if (self%geovals(jv)%vals(jz,jo) > pmax) pmax = self%geovals(jv)%vals(jz,jo)
932 prms = prms + self%geovals(jv)%vals(jz,jo) * self%geovals(jv)%vals(jz,jo)
936 if (kobs > 0) prms = sqrt(prms/real(kobs,kind_real))
951 real(kind_real),
intent(inout) :: mxval
952 integer,
intent(inout) :: iobs, ivar
955 real(kind_real) :: vrms
956 integer :: jv, jo, jz
958 if (.not. self%linit)
then
959 call abor1_ftn(
"ufo_geovals_maxloc: geovals not allocated")
962 mxval = 0.0_kind_real
967 do jo = 1, self%nlocs
970 do jz = 1, self%geovals(jv)%nval
971 vrms = vrms + self%geovals(jv)%vals(jz,jo)**2
974 if ( self%geovals(jv)%nval > 0 )
then
975 vrms = sqrt(vrms/real(self%geovals(jv)%nval,kind_real))
978 if (vrms > mxval)
then
993 use oops_variables_mod
996 character(max_string),
intent(in) :: filename
997 integer,
intent(in) :: loc_multiplier
998 type(c_ptr),
intent(in) :: c_obspace
999 type(oops_variables),
intent(in) :: vars
1001 integer :: nlocs, gv_all_nlocs, nlocs_var
1003 integer :: obs_nlocs
1004 integer :: obs_all_nlocs
1006 integer :: jloc, jloc_start, jloc_end
1009 integer :: ncid, dimid, varid, vartype, ndims
1010 integer,
dimension(3) :: dimids
1014 character(max_string) :: err_msg
1015 character(len=30) :: obs_nlocs_str
1016 character(len=30) :: geo_nlocs_str
1018 integer(c_size_t),
allocatable,
dimension(:) :: dist_indx
1019 integer(c_size_t),
allocatable,
dimension(:) :: obs_dist_indx
1021 real,
allocatable :: field2d(:,:), field1d(:)
1024 call check(
'nf90_open', nf90_open(trim(filename),nf90_nowrite,ncid))
1027 ierr = nf90_inq_dimid(ncid,
"nlocs", dimid)
1028 if(ierr /= nf90_noerr)
then
1029 write(err_msg,*)
"Error: Dimension nlocs not found in ", trim(filename)
1030 call abor1_ftn(err_msg)
1032 call check(
'nf90_inq_dimid', nf90_inq_dimid(ncid,
"nlocs", dimid))
1033 call check(
'nf90_inquire_dimension', nf90_inquire_dimension(ncid, dimid, len = gv_all_nlocs))
1037 obs_all_nlocs = obsspace_get_gnlocs(c_obspace)
1038 obs_nlocs = obsspace_get_nlocs(c_obspace)
1039 allocate(obs_dist_indx(obs_nlocs))
1040 call obsspace_get_index(c_obspace, obs_dist_indx)
1046 if (gv_all_nlocs .lt. (loc_multiplier * obs_all_nlocs))
then
1047 write(obs_nlocs_str, *) loc_multiplier * obs_all_nlocs
1048 write(geo_nlocs_str, *) gv_all_nlocs
1049 write(err_msg,
'(7a)') &
1050 "Error: Number of locations in the geovals file (", &
1051 trim(adjustl(geo_nlocs_str)),
") must be greater than or equal to ", &
1052 "the product of loc_multiplier and number of locations in the ", &
1053 "obs file (", trim(adjustl(obs_nlocs_str)),
")"
1054 call abor1_ftn(err_msg)
1060 if (loc_multiplier >= 0)
then
1061 nlocs = loc_multiplier * obs_nlocs
1062 allocate(dist_indx(nlocs))
1064 do iloc = 1,obs_nlocs
1065 jloc_start = ((obs_dist_indx(iloc) - 1) * loc_multiplier) + 1
1066 jloc_end = obs_dist_indx(iloc) * loc_multiplier
1067 do jloc = jloc_start, jloc_end
1068 dist_indx(iloc_new) = jloc
1069 iloc_new = iloc_new + 1
1073 nlocs = - loc_multiplier * obs_nlocs
1074 allocate(dist_indx(nlocs))
1076 do jloc = 1, - loc_multiplier
1077 do iloc = 1, obs_nlocs
1078 dist_indx(iloc_new) = obs_dist_indx(iloc) + (jloc - 1) * obs_all_nlocs
1079 iloc_new = iloc_new + 1
1087 do ivar = 1, self%nvar
1089 ierr = nf90_inq_varid(ncid, self%variables(ivar), varid)
1090 if(ierr /= nf90_noerr)
then
1091 write(err_msg,*)
"Error: Variable ", trim(self%variables(ivar)),
" not found in ", trim(filename)
1092 call abor1_ftn(err_msg)
1095 call check(
'nf90_inquire_variable', nf90_inquire_variable(ncid, varid, xtype = vartype, &
1096 ndims = ndims, dimids = dimids))
1098 if (ndims == 1)
then
1099 call check(
'nf90_inquire_dimension', nf90_inquire_dimension(ncid, dimids(1), len = nlocs_var))
1100 if (nlocs_var /= gv_all_nlocs)
then
1101 call abor1_ftn(
'ufo_geovals_read_netcdf: var dim /= gv_all_nlocs')
1105 self%geovals(ivar)%nval = nval
1106 allocate(self%geovals(ivar)%vals(nval,nlocs))
1108 allocate(field1d(nlocs_var))
1109 call check(
'nf90_get_var', nf90_get_var(ncid, varid, field1d))
1110 self%geovals(ivar)%vals(1,:) = field1d(dist_indx)
1113 elseif (ndims == 2)
then
1114 call check(
'nf90_inquire_dimension', nf90_inquire_dimension(ncid, dimids(1), len = nval))
1115 call check(
'nf90_inquire_dimension', nf90_inquire_dimension(ncid, dimids(2), len = nlocs_var))
1116 if (nlocs_var /= gv_all_nlocs)
then
1117 call abor1_ftn(
'ufo_geovals_read_netcdf: var dim /= gv_all_nlocs')
1120 self%geovals(ivar)%nval = nval
1121 allocate(self%geovals(ivar)%vals(nval,nlocs))
1122 allocate(field2d(nval, nlocs_var))
1123 call check(
'nf90_get_var', nf90_get_var(ncid, varid, field2d))
1124 self%geovals(ivar)%vals(:,:) = field2d(:,dist_indx)
1128 call abor1_ftn(
'ufo_geovals_read_netcdf: can only read 1d and 2d fields')
1132 where (self%geovals(ivar)%vals > 1.0e08) self%geovals(ivar)%vals = self%missing_value
1136 if (
allocated(dist_indx))
deallocate(dist_indx)
1137 if (
allocated(obs_dist_indx))
deallocate(obs_dist_indx)
1141 call check(
'nf90_close', nf90_close(ncid))
1150 character(max_string),
intent(in) :: filename
1153 integer :: ncid, dimid_nlocs, dimid_nval, dims(2)
1154 integer,
allocatable :: ncid_var(:)
1156 allocate(ncid_var(self%nvar))
1158 call check(
'nf90_create', nf90_create(trim(filename),nf90_hdf5,ncid))
1159 call check(
'nf90_def_dim', nf90_def_dim(ncid,
'nlocs',self%nlocs, dimid_nlocs))
1160 dims(2) = dimid_nlocs
1163 call check(
'nf90_def_dim', &
1164 nf90_def_dim(ncid,trim(self%variables(i))//
"_nval",self%geovals(i)%nval, dimid_nval))
1165 dims(1) = dimid_nval
1166 call check(
'nf90_def_var', &
1167 nf90_def_var(ncid,trim(self%variables(i)),nf90_float,dims,ncid_var(i)))
1170 call check(
'nf90_enddef', nf90_enddef(ncid))
1173 call check(
'nf90_put_var', nf90_put_var(ncid,ncid_var(i),self%geovals(i)%vals(:,:)))
1176 call check(
'nf90_close', nf90_close(ncid))
1177 deallocate(ncid_var)
1183 use netcdf,
only: nf90_noerr, nf90_strerror
1186 integer,
intent (in) :: status
1187 character (len=*),
intent (in) :: action
1188 character(max_string) :: err_msg
1190 if(status /= nf90_noerr)
then
1191 write(err_msg,*)
"During action: ", trim(action),
", received error: ", trim(nf90_strerror(status))
1192 call abor1_ftn(err_msg)
1195 end subroutine check
1202 integer,
intent(in) :: iobs
1205 character(MAXVARLEN) :: varname
1208 do ivar = 1, self%nvar
1209 varname = self%variables(ivar)
1211 if (
associated(geoval))
then
1212 print *,
'geoval test: ', trim(varname), geoval%nval, geoval%vals(:,iobs)
1214 print *,
'geoval test: ', trim(varname),
' doesnt exist'
integer, parameter max_string
subroutine, public ufo_geovals_reorderzdir(self, varname, zdir)
subroutine check(action, status)
subroutine, public ufo_geovals_maxloc(self, mxval, iobs, ivar)
Location where the summed geovals value is maximum.
subroutine, public ufo_geovals_default_constr(self)
subroutine, public ufo_geovals_allocate(self, vars, nlevels)
Deprecated. Rely on ufo_geovals_setup to allocate GeoVaLs instead. Allocates GeoVaLs for vars variabl...
subroutine, public ufo_geovals_random(self)
subroutine, public ufo_geovals_setup(self, vars, nlocs, nvars, nvals)
Initializes and allocates self GeoVaLs with nlocs number of locations for vars variables....
subroutine, public ufo_geovals_write_netcdf(self, filename)
subroutine, public ufo_geovals_normalize(self, other)
Normalization of one GeoVaLs object by another.
subroutine, private ufo_geovals_reset_sec_arg(self, other, nlocs)
subroutine, public ufo_geovals_split(self, other1, other2)
subroutine, public ufo_geovals_read_netcdf(self, filename, loc_multiplier, c_obspace, vars)
subroutine, public ufo_geovals_rms(self, vrms)
subroutine, public ufo_geovals_copy(self, other)
Copy one GeoVaLs object into another.
subroutine, public ufo_geovals_delete(self)
subroutine, public ufo_geovals_analytic_init(self, locs, ic)
Initialize a GeoVaLs object based on an analytic state.
subroutine, public ufo_geovals_diff(self, other)
Difference between two GeoVaLs objects.
subroutine, public ufo_geovals_profmult(self, nlocs, values)
subroutine, public ufo_geovals_copy_one(self, other, loc_index)
Copy one location from GeoVaLs into a new object.
subroutine, public ufo_geovals_minmaxavg(self, kobs, kvar, pmin, pmax, prms)
subroutine, public ufo_geovals_scalmult(self, zz)
subroutine, public ufo_geovals_assign(self, rhs)
subroutine, public ufo_geovals_add(self, other)
Sum of two GeoVaLs objects.
subroutine, public ufo_geovals_print(self, iobs)
subroutine, public ufo_geovals_get_var(self, varname, geoval)
subroutine, public ufo_geovals_partial_setup(self, vars, nlocs)
Deprecated, use ufo_geovals_setup instead. Partially initializes self GeoVaLs with nlocs number of lo...
subroutine, public ufo_geovals_zero(self)
subroutine, public ufo_geovals_abs(self)
subroutine, public ufo_geovals_schurmult(self, other)
Schur product of two GeoVaLs objects.
subroutine, public ufo_geovals_merge(self, other1, other2)
Fortran interface to ufo::Locations.
integer function nlocs(this)
Return the number of observational locations in this Locations object.
Fortran module with various useful routines.
logical function, public cmp_strings(str1, str2)
character(len=maxvarlen), parameter, public var_prsi
integer function, public ufo_vars_getindex(vars, varname)
character(len=maxvarlen), parameter, public var_prs
character(len=maxvarlen), parameter, public var_tv
type to hold interpolated field for one variable, one observation
type to hold interpolated fields required by the obs operators