85 mpp_sync_self, mpp_pe,mpp_npes,mpp_root_pe,&
126 integer,
private,
save ::
nk 137 real,
dimension(:,:,:),
allocatable,
private,
save ::
sum_wgt, nobs
242 mpp_get_fields,
mpp_read, mpp_single, mpp_multi, mpp_netcdf,&
246 character(len=*),
intent(in) :: filename
247 logical,
intent(in),
optional :: localize
248 logical :: found_neighbor,continue_looking
249 integer,
parameter :: max_levels=1000
250 integer :: unit, ndim, nvar, natt, nstation
251 character(len=32) :: fldname, axisname
252 type(
atttype),
allocatable,
dimension(:),
target :: global_atts
253 type(
atttype),
pointer :: version => null()
254 type(
axistype),
pointer :: depth_axis => null(), station_axis => null()
255 type(
axistype),
allocatable,
dimension(:),
target :: axes
256 type(
fieldtype),
allocatable,
dimension(:),
target :: fields
258 type(
fieldtype),
pointer :: field_lon => null(), field_lat => null(), field_probe => null(),&
259 field_time => null(), field_depth => null()
260 type(
fieldtype),
pointer :: field_temp => null(), field_salt => null(), &
261 field_error => null(), field_link => null()
263 real :: lon, lat, time, depth(max_levels), temp(max_levels), salt(max_levels),&
264 error(max_levels), rprobe, profile_error, rlink
265 integer :: nlev, probe, yr, mon, day, hr, minu, sec, kl, outunit
266 integer :: num_levs, num_levs_temp, num_levs_salt,&
267 k, kk, ll, i, i0, j0, k0, nlevs, a, nn, ii, nlinks
268 real :: ri0, rj0, rk0, dx1, dx2, dy1, dy2
269 character(len=128) :: time_units, attname, catt
271 integer :: flag_t(max_levels), flag_s(max_levels), cpe
272 logical :: data_is_local, &
274 logical :: found_temp=.false., found_salt=.false.
275 real,
dimension(max_links,max_levels) :: temp_bfr, salt_bfr, depth_bfr
276 integer,
dimension(max_links,max_levels) :: flag_t_bfr, flag_s_bfr
279 real :: max_prof_depth, zdist
310 call mpp_open(unit,filename,form=mpp_netcdf,fileset=mpp_single,&
311 threading=mpp_multi,action=mpp_rdonly)
312 call mpp_get_info(unit, ndim, nvar, natt, nstation)
315 write(outunit,*)
'Opened profile dataset :',trim(filename)
319 allocate(global_atts(natt))
323 catt = mpp_get_att_char(global_atts(i))
326 version => global_atts(i)
330 if (.NOT.
ASSOCIATED(version))
then 331 call mpp_error(note,
'no version number available for profile file, assuming v0.1a ')
333 write(outunit,*)
'Reading profile dataset version = ',trim(catt)
339 allocate (axes(ndim))
340 call mpp_get_axes(unit,axes)
345 depth_axis => axes(i)
346 case (
'station_index')
347 station_axis => axes(i)
351 if (.NOT.
ASSOCIATED(depth_axis) .or. .NOT.
ASSOCIATED(station_axis))
then 352 call mpp_error(fatal,
'depth and/or station axes do not exist in input file')
359 allocate(fields(nvar))
360 call mpp_get_fields(unit,fields)
365 field_lon => fields(i)
367 field_lat => fields(i)
369 field_probe => fields(i)
371 field_time => fields(i)
373 field_temp => fields(i)
375 field_salt => fields(i)
377 field_depth => fields(i)
379 field_link => fields(i)
381 field_error => fields(i)
387 if (nlevs > max_levels)
call mpp_error(fatal,
'increase parameter max_levels ')
392 write(outunit,*)
'There are ', nstation,
' records in this dataset' 393 write(outunit,*)
'Searching for profiles matching selection criteria ...' 395 if (
ASSOCIATED(field_temp)) found_temp=.true.
396 if (
ASSOCIATED(field_salt)) found_salt=.true.
398 if (.not. found_temp .and. .not. found_salt)
then 399 write(outunit,*)
'temp or salt not found in profile file' 404 if (found_temp)
call mpp_get_atts(field_temp,missing=temp_missing)
405 if (found_salt)
call mpp_get_atts(field_salt,missing=salt_missing)
410 write(outunit,*)
'temperature and salinity where available' 412 write(outunit,*)
'temperature only records' 425 call mpp_read(unit,field_lon,lon,tindex=i)
426 call mpp_read(unit,field_lat,lat, tindex=i)
427 call mpp_read(unit,field_time,time,tindex=i)
428 call mpp_read(unit,field_depth,depth(1:nlevs),tindex=i)
429 if (found_temp)
call mpp_read(unit,field_temp,temp(1:nlevs),tindex=i)
430 if (found_salt)
call mpp_read(unit,field_salt,salt(1:nlevs),tindex=i)
432 if (
ASSOCIATED(field_error))
then 433 call mpp_read(unit,field_error,profile_error,tindex=i)
435 if (
ASSOCIATED(field_probe))
then 436 call mpp_read(unit, field_probe, rprobe,tindex=i)
438 if (
ASSOCIATED(field_link))
then 439 call mpp_read(unit,field_link,rlink,tindex=i)
444 data_is_local = .false.
447 if (lon .lt.
x_grid(
isg-1) ) lon = lon + 360.0
448 if (lon .gt.
x_grid(
ieg+1) ) lon = lon - 360.0
456 lat <
y_grid(
jec+1)) data_is_local = .true.
466 call mpp_error(fatal,
'maximum number of profiles exceeded.& 467 &Resize parameter max_profiles in ocean_obs_mod')
493 flag_t(k) = 0;flag_s(k) = 0
495 if (.not.found_salt)
then 499 if (depth(k) .eq. depth_missing .or. depth(k) .lt.
depth_min&
506 if (found_temp .and. flag_t(k) .eq. 0)
then 507 if (temp(k) .eq. temp_missing .or. temp(k) .lt.
temp_min&
513 num_levs_temp = num_levs_temp+1
516 if (found_salt .and. flag_s(k) .eq. 0)
then 517 if (salt(k) .eq. salt_missing .or. salt(k) .lt.
salt_min&
522 num_levs_salt = num_levs_salt+1
533 do while (rlink > 0.0 .and. nlinks .lt.
max_links)
538 call mpp_read(unit,field_depth,depth_bfr(nlinks,1:nlevs),tindex=ii)
539 if (found_temp)
call mpp_read(unit,field_temp,temp_bfr(nlinks,1:nlevs),tindex=ii)
540 if (found_salt)
call mpp_read(unit,field_salt,salt_bfr(nlinks,1:nlevs),tindex=ii)
541 call mpp_read(unit,field_link,rlink,tindex=ii)
551 if (depth_bfr(nn,k) .eq. depth_missing .or.&
558 if (found_temp .and. flag_t_bfr(nn,k) .eq. 0)
then 559 if (temp_bfr(nn,k) .eq. temp_missing .or.&
566 num_levs_temp = num_levs_temp+1
569 if (found_salt .and. flag_s_bfr(nn,k) .eq. 0)
then 570 if (salt_bfr(nn,k) .eq. salt_missing .or.&
577 num_levs_salt = num_levs_salt+1
584 num_levs =
max(num_levs_temp,num_levs_salt)
586 if (num_levs == 0)
then 587 if (i .gt. nstation)
continue = .false.
593 if (num_levs_temp .gt. 0)
then 601 if (num_levs_salt .gt. 0)
then 610 if (probe < 1 ) probe = 0
618 if(num_levs_salt .gt. 0)
then 625 if (flag_t(k) .eq. 0)
then 632 if (found_salt .and. flag_s(k) .eq. 0)
then 642 if (flag_t_bfr(nn,k) .eq. 0)
then 649 if (found_salt .and. flag_s_bfr(nn,k) .eq. 0)
then 671 if (i0 < 0 .or. j0 < 0)
then 674 if (i0 >
ieg .or. j0 >
jeg)
then 675 call mpp_error(fatal,
'grid lat/lon index is out of bounds ')
678 call mpp_error(fatal,
'grid lat/lon index is out of bounds ')
681 call mpp_error(fatal,
'grid lat/lon index is out of bounds ')
687 if (
grd%mask(i0,j0,1) == 0.0 .or. &
688 grd%mask(i0+1,j0,1) == 0.0 .or. &
689 grd%mask(i0,j0+1,1) == 0.0 .or. &
690 grd%mask(i0+1,j0+1,1) == 0.0)
then 715 if (k0 .gt.
size(
grd%z)-1 )
then 716 write(*,*)
'k0 out of bounds, rk0,k0= ',rk0,k0
717 write(*,*)
'Z_bound= ',
grd%z_bound
728 if (i0 .lt. 0 .or. j0 .lt. 0 .or. k0 .lt. 0)
then 729 write(*,*)
'profile index out of bounds' 730 write(*,*)
'i0,j0,k0=',i0,j0,k0
736 if (
grd%mask(i0,j0,k0) == 0.0 .or. &
737 grd%mask(i0+1,j0,k0) == 0.0 .or. &
738 grd%mask(i0,j0+1,k0) == 0.0 .or. &
739 grd%mask(i0+1,j0+1,k0) == 0.0)
then 742 if (
grd%mask(i0,j0,k0+1) == 0.0 .or. &
743 grd%mask(i0+1,j0,k0+1) == 0.0 .or. &
744 grd%mask(i0,j0+1,k0+1) == 0.0 .or. &
745 grd%mask(i0+1,j0+1,k0+1) == 0.0)
then 761 found_neighbor=.false.
766 found_neighbor = .false.
767 continue_looking = .true.
768 do while (continue_looking .and. kk .ge. 1)
775 continue_looking = .false.
776 found_neighbor = .true.
783 continue_looking = .true.
791 continue_looking = .false.
792 found_neighbor = .true.
811 if (i .gt. nstation)
continue = .false.
834 subroutine get_obs(model_time, Prof, Sfc, nprof, nsfc)
840 type(
time_type),
intent(in) :: model_time
843 integer,
intent(inout) :: nprof, nsfc
845 integer :: i,k,yr,mon,day,hr,minu,sec,a,mon_obs,yr_obs, outunit
847 character(len=1) :: cchar
853 write(outunit,*)
'Gathering profiles for current analysis time' 854 call get_date(model_time,yr,mon,day,hr,minu,sec)
855 write(outunit,
'(a,i4,a,i2,a,i2)')
'Current yyyy/mm/dd= ',yr,
'/',mon,
'/',day
863 write(*,*)
'in get_obs prof time: yy/mm/dd= ',yr,mon,day
866 if (
profiles(i)%time <= model_time)
then 867 tdiff = model_time -
profiles(i)%time
869 tdiff =
profiles(i)%time - model_time
873 write(*,*)
'Prof%accepted=',
profiles(i)%accepted
879 if (nprof >
size(prof,1)) &
880 call mpp_error(fatal,
'increase size of Prof array before call to get_obs')
882 prof(nprof)%tdiff = tdiff
885 write(*,
'(a,i3,a,2f10.5)')
'Accepted profile #',i,
' : lon,lat= ',prof(nprof)%lon,prof(nprof)%lat
886 do k=1,prof(nprof)%levels
887 if (prof(nprof)%nvar .eq. 2)
then 888 write(*,
'(a,i3,a,2f10.5,2i2,2f8.5)')
'Profile #',i,
' : temp,salt,flag_t,flag_s,ms_t,ms_s= ',&
889 prof(nprof)%data_t(k),prof(nprof)%data_s(k),prof(nprof)%flag_t(k),prof(nprof)%flag_s(k),&
890 prof(nprof)%ms_t(k),prof(nprof)%ms_s(k)
892 write(*,
'(a,i3,a,2f10.5)')
'Profile #',i,
' : temp,flag_t= ',prof(nprof)%data_t(k),prof(nprof)%flag_t(k)
900 write(*,
'(a,i3,a,2f10.5)')
'Rejected profile #',i,
' : lon,lat= ',prof(i)%lon,prof(i)%lat
901 do k=1,prof(i)%levels
902 if (prof(i)%nvar .eq. 2)
then 903 write(*,
'(a,i3,a,2f10.5,2i2)')
'Profile #',i,
' : temp,salt,flag_t,flag_s= ',prof(i)%data_t(k),prof(i)%data_s(k),prof(i)%flag_t(k),prof(i)%flag_s(k)
905 write(*,
'(a,i3,a,2f10.5)')
'Profile #',i,
' : temp,flag_t= ',prof(i)%data_t(k),prof(i)%flag_t(k)
915 write(outunit,*)
'A total of ',a,
' profiles are being used for the current analysis step' 925 type(
domain2d),
intent(in) :: domain
926 type(
grid_type),
target,
intent(in) :: grid
927 logical,
intent(in),
optional :: localize
930 integer :: ioun, ierr, io_status
932 #ifdef INTERNAL_FILE_NML 936 ioun = open_namelist_file()
937 read(ioun,nml=oda_core_nml,iostat = io_status)
939 call close_file(ioun)
976 type(ocean_profile_type),
dimension(:),
intent(inout) ::Model_obs
977 real,
dimension(isd:ied,jsd:jed,nk) ,
intent(in) :: fg_t
978 real,
dimension(isd:ied,jsd:jed,nk) ,
intent(in),
optional :: fg_s
980 integer :: n, i0, j0, k, num_prof, k0
983 character(len=128) :: mesg
985 num_prof =
size(model_obs)
990 i0 = floor(model_obs(n)%i_index)
991 j0 = floor(model_obs(n)%j_index)
992 a = model_obs(n)%i_index - i0
993 b = model_obs(n)%j_index - j0
995 if (a >= 1.0 .or. a < 0.0 )
call mpp_error(fatal)
996 if (b >= 1.0 .or. b < 0.0 )
call mpp_error(fatal)
999 if (i0 <
isc-1 .or. i0 >
iec)
then 1000 write(mesg,
'(a,i4,2x,i4)')
'out of bounds in forward_obs: i0,j0= ',i0,j0
1004 if (j0 <
jsc-1 .or. j0 >
jec)
then 1005 write(mesg,*)
'out of bounds in forward_obs: i0,j0= ',i0,j0
1009 if (
ASSOCIATED(model_obs(n)%data_t) .and. model_obs(n)%accepted)
then 1011 if (
ASSOCIATED(model_obs(n)%Forward_model%wgt))&
1012 model_obs(n)%Forward_model%wgt => null()
1013 allocate(model_obs(n)%Forward_model%wgt(2,2,2,model_obs(n)%levels))
1015 model_obs(n)%Forward_model%wgt = 0.0
1017 do k = 1, model_obs(n)%levels
1018 if (model_obs(n)%flag_t(k) .eq. 0)
then 1019 k0 = floor(model_obs(n)%k_index(k))
1020 if (k0 < 1 .or. k0 >
grd%nk-1)
then 1021 write(mesg,*)
'out of bounds in forward_obs: k0= ',k0
1024 c = model_obs(n)%k_index(k) - k0
1026 if (c >= 1.0 .or. c < 0.0 )
call mpp_error(fatal)
1028 model_obs(n)%Forward_model%wgt(1,1,1,k) = (1.0-a)*(1.0-b)*(1.0-c)
1029 model_obs(n)%Forward_model%wgt(2,1,1,k) = a*(1.0-b)*(1.0-c)
1030 model_obs(n)%Forward_model%wgt(1,2,1,k) = (1.0-a)*b*(1.0-c)
1031 model_obs(n)%Forward_model%wgt(2,2,1,k) = a*b*(1.0-c)
1032 model_obs(n)%Forward_model%wgt(1,1,2,k) = (1.0-a)*(1.0-b)*c
1033 model_obs(n)%Forward_model%wgt(2,1,2,k) = a*(1.0-b)*c
1034 model_obs(n)%Forward_model%wgt(1,2,2,k) = (1.0-a)*b*c
1035 model_obs(n)%Forward_model%wgt(2,2,2,k) = a*b*c
1038 model_obs(n)%Forward_model%wgt(1,1,1,k)
1040 model_obs(n)%Forward_model%wgt(2,1,1,k)
1042 model_obs(n)%Forward_model%wgt(1,2,1,k)
1044 model_obs(n)%Forward_model%wgt(2,2,1,k)
1046 model_obs(n)%Forward_model%wgt(1,1,2,k)
1048 model_obs(n)%Forward_model%wgt(2,1,2,k)
1050 model_obs(n)%Forward_model%wgt(1,2,2,k)
1052 model_obs(n)%Forward_model%wgt(2,2,2,k)
1055 model_obs(n)%data_t(k) = &
1056 fg_t(i0,j0,k0)*model_obs(n)%Forward_model%wgt(1,1,1,k) &
1057 + fg_t(i0+1,j0,k0)*model_obs(n)%Forward_model%wgt(2,1,1,k) &
1058 + fg_t(i0,j0+1,k0)*model_obs(n)%Forward_model%wgt(1,2,1,k) &
1059 + fg_t(i0+1,j0+1,k0)*model_obs(n)%Forward_model%wgt(2,2,1,k) &
1060 + fg_t(i0,j0,k0+1)*model_obs(n)%Forward_model%wgt(1,1,2,k) &
1061 + fg_t(i0+1,j0,k0+1)*model_obs(n)%Forward_model%wgt(2,1,2,k) &
1062 + fg_t(i0,j0+1,k0+1)*model_obs(n)%Forward_model%wgt(1,2,2,k) &
1063 + fg_t(i0+1,j0+1,k0+1)*model_obs(n)%Forward_model%wgt(2,2,2,k)
1065 if (
ASSOCIATED(model_obs(n)%data_s) .and.
PRESENT(fg_s))
then 1066 model_obs(n)%data_s(k) = &
1067 fg_s(i0,j0,k0)*model_obs(n)%Forward_model%wgt(1,1,1,k) &
1068 + fg_s(i0+1,j0,k0)*model_obs(n)%Forward_model%wgt(2,1,1,k) &
1069 + fg_s(i0,j0+1,k0)*model_obs(n)%Forward_model%wgt(1,2,1,k) &
1070 + fg_s(i0+1,j0+1,k0)*model_obs(n)%Forward_model%wgt(2,2,1,k) &
1071 + fg_s(i0,j0,k0+1)*model_obs(n)%Forward_model%wgt(1,1,2,k) &
1072 + fg_s(i0+1,j0,k0+1)*model_obs(n)%Forward_model%wgt(2,1,2,k) &
1073 + fg_s(i0,j0+1,k0+1)*model_obs(n)%Forward_model%wgt(1,2,2,k) &
1074 + fg_s(i0+1,j0+1,k0+1)*model_obs(n)%Forward_model%wgt(2,2,2,k)
1077 if (
ASSOCIATED(model_obs(n)%data_t))
then 1080 if (
ASSOCIATED(model_obs(n)%data_s))
then 1097 type(ocean_surface_type),
intent(in) :: Sfc
1098 type(ocean_dist_type),
intent(in) :: Guess
1099 type(ocean_surface_type),
intent(inout) :: Diff
1110 type(ocean_profile_type),
dimension(:),
intent(in) :: Obs
1111 real,
dimension(isd:ied,jsd:jed,nk),
intent(inout) :: model_t
1112 real,
dimension(isd:ied,jsd:jed,nk),
intent(inout),
optional :: model_s
1115 integer :: i0,j0,k0,k,n
1118 if (
PRESENT(model_s)) model_s = 0.0
1121 if (
ASSOCIATED(obs(n)%data_t) .and. obs(n)%accepted)
then 1122 i0 = floor(obs(n)%i_index)
1123 j0 = floor(obs(n)%j_index)
1127 if (i0 <
isd .or. i0 >
ied-1) cycle
1128 if (j0 <
jsd .or. j0 >
jed-1) cycle
1130 if (.not.
ASSOCIATED(obs(n)%Forward_model%wgt))
call mpp_error(fatal,
'forward operator not associated with obs')
1132 do k=1, obs(n)%levels
1133 if (obs(n)%flag_t(k) .eq. 0)
then 1134 k0 = floor(obs(n)%k_index(k))
1135 if (k0 < 1 .or. k0 >
grd%nk-1)
call mpp_error(fatal,
'profile k indx out of bnds')
1137 tmp = obs(n)%data_t(k)
1138 model_t(i0,j0,k0) = model_t(i0,j0,k0) + tmp*obs(n)%Forward_model%wgt(1,1,1,k)
1139 model_t(i0+1,j0,k0) = model_t(i0+1,j0,k0) + tmp*obs(n)%Forward_model%wgt(2,1,1,k)
1140 model_t(i0,j0+1,k0) = model_t(i0,j0+1,k0) + tmp*obs(n)%Forward_model%wgt(1,2,1,k)
1141 model_t(i0+1,j0+1,k0) = model_t(i0+1,j0+1,k0) + tmp*obs(n)%Forward_model%wgt(2,2,1,k)
1142 model_t(i0,j0,k0+1) = model_t(i0,j0,k0+1) + tmp*obs(n)%Forward_model%wgt(1,1,2,k)
1143 model_t(i0+1,j0,k0+1) = model_t(i0+1,j0,k0+1) + tmp*obs(n)%Forward_model%wgt(2,1,2,k)
1144 model_t(i0,j0+1,k0+1) = model_t(i0,j0+1,k0+1) + tmp*obs(n)%Forward_model%wgt(1,2,2,k)
1145 model_t(i0+1,j0+1,k0+1) = model_t(i0+1,j0+1,k0+1) + tmp*obs(n)%Forward_model%wgt(2,2,2,k)
1147 if (
PRESENT(model_s))
then 1149 tmp = obs(n)%data_s(k)
1150 model_s(i0,j0,k0) = model_s(i0,j0,k0) + tmp*obs(n)%Forward_model%wgt(1,1,1,k)
1151 model_s(i0+1,j0,k0) = model_s(i0+1,j0,k0) + tmp*obs(n)%Forward_model%wgt(2,1,1,k)
1152 model_s(i0,j0+1,k0) = model_s(i0,j0+1,k0) + tmp*obs(n)%Forward_model%wgt(1,2,1,k)
1153 model_s(i0+1,j0+1,k0) = model_s(i0+1,j0+1,k0) + tmp*obs(n)%Forward_model%wgt(2,2,1,k)
1154 model_s(i0,j0,k0+1) = model_s(i0,j0,k0+1) + tmp*obs(n)%Forward_model%wgt(1,1,2,k)
1155 model_s(i0+1,j0,k0+1) = model_s(i0+1,j0,k0+1) + tmp*obs(n)%Forward_model%wgt(2,1,2,k)
1156 model_s(i0,j0+1,k0+1) = model_s(i0,j0+1,k0+1) + tmp*obs(n)%Forward_model%wgt(1,2,2,k)
1157 model_s(i0+1,j0+1,k0+1) = model_s(i0+1,j0+1,k0+1) + tmp*obs(n)%Forward_model%wgt(2,2,2,k)
1174 if (
PRESENT(model_s))
then 1187 type(ocean_surface_type),
dimension(:),
intent(in) :: Obs
1188 real,
dimension(isd:ied,jsd:jed,nk),
intent(inout) :: model
1195 type(ocean_profile_type),
dimension(:),
target,
intent(in) :: Obs1
1196 type(ocean_profile_type),
dimension(:),
intent(inout) :: Obs2
1201 if (
size(obs1) .ne.
size(obs2))
call mpp_error(fatal)
1205 obs2(n)%Forward_model%wgt => obs1(n)%Forward_model%wgt
1214 type(ocean_surface_type),
target,
intent(in) :: Obs1
1215 type(ocean_surface_type),
intent(inout) :: Obs2
1223 type(ocean_profile_type),
dimension(:),
intent(in) :: prof1
1224 type(ocean_profile_type),
dimension(:),
intent(in) :: prof2
1225 type(ocean_profile_type),
dimension(:),
intent(inout) :: Diff
1229 if (
size(prof1) .ne.
size(prof2) )
call mpp_error(fatal)
1231 if (
size(prof1) .ne.
size(diff) )
call mpp_error(fatal)
1235 do k=1,prof1(n)%levels
1236 if (prof1(n)%flag_t(k) .eq. 0)
then 1237 diff(n)%data_t(k) = prof2(n)%data_t(k)-prof1(n)%data_t(k)
1241 if (abs(diff(n)%data_t(k)) .gt.
max_misfit)
then 1242 diff(n)%flag_t(k) = 1
1244 if (
ASSOCIATED(prof1(n)%data_s))
then 1245 if (prof1(n)%flag_s(k) .eq. 0)
then 1246 diff(n)%data_s(k) = prof2(n)%data_s(k)-prof1(n)%data_s(k)
1250 if (abs(diff(n)%data_s(k)) .gt.
max_misfit)
then 1251 diff(n)%flag_s(k) = 1
1262 type(ocean_surface_type),
dimension(:),
intent(in) :: prof1, prof2
1263 type(ocean_surface_type),
dimension(:),
intent(inout) :: Diff
1270 type(ocean_profile_type),
dimension(:),
intent(in) :: obs_in
1271 type(ocean_profile_type),
dimension(:),
intent(inout) :: obs_out
1276 if (
size(obs_in) .ne.
size(obs_out))
call mpp_error(fatal,&
1277 'size mismatch in call to copy_obs_prof')
1282 obs_out(n)%nvar = obs_in(n)%nvar
1283 obs_out(n)%project = obs_in(n)%project
1284 obs_out(n)%probe = obs_in(n)%probe
1285 obs_out(n)%ref_inst = obs_in(n)%ref_inst
1286 obs_out(n)%wod_cast_num = obs_in(n)%wod_cast_num
1287 obs_out(n)%fix_depth = obs_in(n)%fix_depth
1288 obs_out(n)%ocn_vehicle = obs_in(n)%ocn_vehicle
1289 obs_out(n)%database_id = obs_in(n)%database_id
1290 obs_out(n)%levels = obs_in(n)%levels
1291 obs_out(n)%profile_flag = obs_in(n)%profile_flag
1292 obs_out(n)%profile_flag_s = obs_in(n)%profile_flag_s
1293 obs_out(n)%lon = obs_in(n)%lon
1294 obs_out(n)%lat = obs_in(n)%lat
1295 obs_out(n)%accepted = obs_in(n)%accepted
1296 ALLOCATE(obs_out(n)%depth(obs_in(n)%levels))
1297 obs_out(n)%depth(:) = obs_in(n)%depth(:)
1298 ALLOCATE(obs_out(n)%data_t(obs_in(n)%levels))
1299 obs_out(n)%data_t(:) = obs_in(n)%data_t(:)
1300 ALLOCATE(obs_out(n)%flag_t(obs_in(n)%levels))
1301 obs_out(n)%flag_t(:) = obs_in(n)%flag_t(:)
1302 if (
ASSOCIATED(obs_in(n)%data_s))
then 1303 ALLOCATE(obs_out(n)%data_s(obs_in(n)%levels))
1304 obs_out(n)%data_s(:) = obs_in(n)%data_s(:)
1305 ALLOCATE(obs_out(n)%flag_s(obs_in(n)%levels))
1306 obs_out(n)%flag_s(:) = obs_in(n)%flag_s(:)
1309 obs_out(n)%time = obs_in(n)%time
1310 obs_out(n)%yyyy = obs_in(n)%yyyy
1311 obs_out(n)%mmdd = obs_in(n)%mmdd
1312 obs_out(n)%i_index = obs_in(n)%i_index
1313 obs_out(n)%j_index = obs_in(n)%j_index
1314 ALLOCATE(obs_out(n)%k_index(obs_in(n)%levels))
1315 obs_out(n)%k_index = obs_in(n)%k_index
1316 ALLOCATE(obs_out(n)%ms_t(obs_in(n)%levels))
1317 obs_out(n)%ms_t = obs_in(n)%ms_t
1318 if (
ASSOCIATED(obs_in(n)%ms_s))
then 1319 ALLOCATE(obs_out(n)%ms_s(obs_in(n)%levels))
1320 obs_out(n)%ms_s = obs_in(n)%ms_s
1325 obs_out(n)%tdiff = obs_in(n)%tdiff
1326 obs_out(n)%nbr_index = obs_in(n)%nbr_index
1327 obs_out(n)%nbr_dist = obs_in(n)%nbr_dist
1328 if (
ASSOCIATED(obs_in(n)%Model_grid)) &
1329 obs_out(n)%Model_grid => obs_in(n)%Model_Grid
1335 type(ocean_surface_type),
dimension(:),
intent(in) :: Obs_in
1336 type(ocean_surface_type),
dimension(:),
intent(inout) :: Obs_out
1347 type(ocean_profile_type),
dimension(:),
intent(inout) :: Prof
1348 integer :: secs, days, n, k, secs_w, days_w, m
1352 call get_time(prof(n)%tdiff,secs, days)
1355 tfac = (days + secs/86400.) / days_w
1356 tfac = 1. -
min(1.,tfac)
1359 do k=1,prof(n)%levels
1360 prof(n)%ms_t(k) = 1.0/
max(1.e-1,tfac) * prof(n)%ms_t(k)
1361 if (
ASSOCIATED(prof(n)%data_s))
then 1362 prof(n)%ms_s(k) = 1.0/
max(1.e-1,tfac) * prof(n)%ms_s(k)
1371 type(ocean_surface_type),
intent(inout) :: Diff
1380 type(ocean_profile_type),
dimension(:),
intent(inout) :: Obs
1386 do k = 1, obs(n)%levels
1387 ims = 1./obs(n)%ms_t(k)
1388 if (obs(n)%flag_t(k) .eq. 0) obs(n)%data_t(k) = ims*obs(n)%data_t(k)
1389 if (
ASSOCIATED(obs(n)%data_s))
then 1390 ims = 1/obs(n)%ms_s(k)
1391 if (obs(n)%flag_s(k) .eq. 0) obs(n)%data_s(k) = ims*obs(n)%data_s(k)
1400 real,
dimension(:),
intent(in) :: a
1401 type(ocean_surface_type),
intent(inout) :: Obs
1415 character(len=*),
intent(in) :: cs
1417 character :: ca(len(cs))
1419 integer,
parameter :: co=iachar(
'a')-iachar(
'A')
1421 ca = transfer(cs,
"x",len(cs))
1422 where (ca >=
"A" .and. ca <=
"Z") ca = achar(iachar(ca)+co)
1430 use mpp_io_mod,
only : mpp_open, mpp_ascii, mpp_rdonly, mpp_multi, mpp_single
1433 logical,
intent(in),
optional :: localize
1435 integer :: data_window = 15
1441 character(len=128) :: filename
1442 character(len=16) :: file_type
1443 end type obs_entry_type
1447 character(len=128) :: input_files(max_files) =
'' 1448 integer :: nfiles, filetype(max_files), ioun, io_status, ierr,&
1450 character(len=256) :: record
1451 type(obs_entry_type) :: tbl_entry
1453 #ifdef INTERNAL_FILE_NML 1457 ioun = open_namelist_file()
1458 read(ioun,nml=ocean_obs_nml,iostat = io_status)
1460 call close_file(ioun)
1467 if (file_exist(
'ocean_obs_table') )
then 1468 call mpp_open(unit,
'ocean_obs_table',action=mpp_rdonly)
1470 do while (nfiles <= max_files)
1471 read(unit,
'(a)',end=99,err=98) record
1473 if (record(1:1) ==
'#') cycle
1474 read(record,*,err=98,end=98) tbl_entry
1476 input_files(nfiles) = tbl_entry%filename
1477 select case (trim(tbl_entry%file_type))
1485 call mpp_error(fatal,
'error in obs_table entry format')
1489 call mpp_error(fatal,
' number of obs files exceeds max_files parameter')
1515 if (
grd%cyclic)
then 1534 call mpp_error(fatal,
'filetype not currently supported')
1545 type(ocean_profile_type),
intent(inout) :: Prof
1548 real :: dtdz, err, a1, a2
1550 if (.not.
ASSOCIATED(prof%ms_t))
then 1551 allocate(prof%ms_t(prof%levels))
1555 do k=2,prof%levels - 1
1556 if (prof%flag_t(k-1) .eq. 0 .and. prof%flag_t(k+1) .eq. 0)
then 1557 dtdz = (prof%data_t(k+1)-prof%data_t(k-1))/(prof%depth(k+1)-prof%depth(k-1))
1560 prof%ms_t(k) = err*err
1561 if (
ASSOCIATED(prof%data_s))
then 1562 dtdz = (prof%data_s(k+1)-prof%data_s(k-1))/(prof%depth(k+1)-prof%depth(k-1))
1565 prof%ms_s(k) = err*err
1576 logical,
intent(in),
optional :: localize
1577 logical :: localize_data = .true.
1578 integer,
parameter :: nlevels = 100
1579 real,
parameter :: width_trans = 250.0
1580 real,
parameter :: bot_depth = 2000.0
1581 real,
allocatable,
dimension(:) :: lon,lat, sst, sss, bot_temp, bot_salt, depth
1582 real,
allocatable,
dimension(:,:) :: temp, salt, temp_error, salt_error
1583 integer,
allocatable,
dimension(:) :: yr, mon, day, hr, mm, ss
1584 integer :: nstation, unit, n, noobs, i, k
1585 real :: ri0,rj0,rk0, mid_depth, dtdf, temp_cent, depthC_I_trans, dsdf, salt_cent
1586 type(time_type) :: profile_time
1587 logical :: data_is_local
1588 integer :: model, parse_ok, cpe
1590 real :: dz, a, dx1, dx2, dy1, dy2
1593 character(len=32) :: fld_type, fld_name
1594 type(method_type),
allocatable,
dimension(:) :: ocean_obs_methods
1596 if (
PRESENT(localize)) localize_data = localize
1610 allocate(ocean_obs_methods(noobs))
1611 allocate(lon(noobs),lat(noobs), yr(noobs), mon(noobs), day(noobs), &
1612 hr(noobs), mm(noobs), ss(noobs), &
1613 sst(noobs), sss(noobs), bot_temp(noobs), bot_salt(noobs))
1614 allocate(temp(noobs,nlevels), salt(noobs,nlevels), temp_error(noobs,nlevels), salt_error(noobs,nlevels))
1615 allocate(depth(nlevels))
1619 parse_ok =
parse(ocean_obs_methods(i)%method_control,
'lon',lon(i))
1620 if (parse_ok == 0)
call mpp_error(fatal,
'==>Error oda_core_mod: idealized_ocean_profiles table entry error')
1621 if (lon(i) .lt.
x_grid(
isg) ) lon(i) = lon(i) + 360.0
1622 if (lon(i) .gt.
x_grid(
ieg) ) lon(i) = lon(i) - 360.0
1623 parse_ok =
parse(ocean_obs_methods(i)%method_control,
'lat',lat(i))
1624 if (parse_ok == 0)
call mpp_error(fatal,
'==>Error oda_core_mod: idealized_ocean_profiles table entry error')
1625 parse_ok =
parse(ocean_obs_methods(i)%method_control,
'yr',yr(i))
1626 if (parse_ok == 0)
call mpp_error(fatal,
'==>Error oda_core_mod: idealized_ocean_profiles table entry error')
1627 parse_ok =
parse(ocean_obs_methods(i)%method_control,
'mon',mon(i))
1628 if (parse_ok == 0)
call mpp_error(fatal,
'==>Error oda_core_mod: idealized_ocean_profiles table entry error')
1629 parse_ok =
parse(ocean_obs_methods(i)%method_control,
'day',day(i))
1630 if (parse_ok == 0)
call mpp_error(fatal,
'==>Error oda_core_mod: idealized_ocean_profiles table entry error')
1631 parse_ok =
parse(ocean_obs_methods(i)%method_control,
'hr',hr(i))
1632 if (parse_ok == 0)
call mpp_error(fatal,
'==>Error oda_core_mod: idealized_ocean_profiles table entry error')
1633 parse_ok =
parse(ocean_obs_methods(i)%method_control,
'mm',mm(i))
1634 if (parse_ok == 0)
call mpp_error(fatal,
'==>Error oda_core_mod: idealized_ocean_profiles table entry error')
1635 parse_ok =
parse(ocean_obs_methods(i)%method_control,
'ss',ss(i))
1636 if (parse_ok == 0)
call mpp_error(fatal,
'==>Error oda_core_mod: idealized_ocean_profiles table entry error')
1637 parse_ok =
parse(ocean_obs_methods(i)%method_control,
'sst',sst(i))
1638 if (parse_ok == 0)
call mpp_error(fatal,
'==>Error oda_core_mod: idealized_ocean_profiles table entry error')
1639 parse_ok =
parse(ocean_obs_methods(i)%method_control,
'sss',sss(i))
1640 if (parse_ok == 0)
call mpp_error(fatal,
'==>Error oda_core_mod: idealized_ocean_profiles table entry error')
1641 parse_ok =
parse(ocean_obs_methods(i)%method_control,
'bot_temp',bot_temp(i))
1642 if (parse_ok == 0)
call mpp_error(fatal,
'==>Error oda_core_mod: idealized_ocean_profiles table entry error')
1643 parse_ok =
parse(ocean_obs_methods(i)%method_control,
'bot_salt',bot_salt(i))
1644 if (parse_ok == 0)
call mpp_error(fatal,
'==>Error oda_core_mod: idealized_ocean_profiles table entry error')
1647 if (noobs == 0 )
then 1648 call mpp_error(fatal,
'==> NOTE from oda_core_mod: no idealized profiles given in field table')
1652 dz = bot_depth/(nlevels-1)
1658 mid_depth = bot_depth/2.0
1659 depthc_i_trans = mid_depth / width_trans
1661 dtdf = (bot_temp(i) - sst(i)) / (2.0*atan(1.0) + atan(depthc_i_trans))
1662 temp_cent = sst(i) + dtdf * atan(depthc_i_trans)
1665 temp(i,k) = temp_cent + dtdf * atan((depth(k) - mid_depth)/width_trans)
1667 temp(i,nlevels) = bot_temp(i)
1669 dsdf = (bot_salt(i) - sss(i)) / (2.0*atan(1.0) + atan(depthc_i_trans))
1670 salt_cent = sss(i) + dsdf * atan(depthc_i_trans)
1673 salt(i,k) = salt_cent + dsdf * atan((depth(k) - mid_depth)/width_trans)
1675 salt(i,nlevels) = bot_salt(i)
1682 data_is_local = .false.
1691 lat(i) <
y_grid(
jec+1)) data_is_local = .true.
1694 profile_time =
set_date(yr(i),mon(i),day(i),hr(i),mm(i),ss(i))
1696 if ( data_is_local .OR. .NOT.localize_data)
then 1705 call mpp_error(fatal,
'maximum number of profiles exceeded. Resize parameter max_profiles in ocean_obs_mod')
1747 if (i0 < 0 .or. j0 < 0)
then 1750 if (i0 >
ieg+1 .or. j0 >
jeg+1)
then 1751 call mpp_error(fatal,
'grid lat/lon index is out of bounds ')
1753 if (i0 <
isc-1 .or. i0 >
iec)
then 1754 call mpp_error(fatal,
'grid lat/lon index is out of bounds ')
1756 if (j0 <
jsc-1 .or. j0 >
jec)
then 1757 call mpp_error(fatal,
'grid lat/lon index is out of bounds ')
1760 if (
grd%mask(i0,j0,1) == 0.0 .or. &
1761 grd%mask(i0+1,j0,1) == 0.0 .or. &
1762 grd%mask(i0,j0+1,1) == 0.0 .or. &
1763 grd%mask(i0+1,j0+1,1) == 0.0)
then 1784 if (k0 .gt.
size(
grd%z)-1 )
then 1785 write(*,*)
'k0 out of bounds, rk0,k0= ',rk0,k0
1786 write(*,*)
'Z_bound= ',
grd%z_bound
1794 if (
grd%mask(i0,j0,k0) == 0.0 .or. &
1795 grd%mask(i0+1,j0,k0) == 0.0 .or. &
1796 grd%mask(i0,j0+1,k0) == 0.0 .or. &
1797 grd%mask(i0+1,j0+1,k0) == 0.0)
then 1800 if (
grd%mask(i0,j0,k0+1) == 0.0 .or. &
1801 grd%mask(i0+1,j0,k0+1) == 0.0 .or. &
1802 grd%mask(i0,j0+1,k0+1) == 0.0 .or. &
1803 grd%mask(i0+1,j0+1,k0+1) == 0.0)
then 1835 type(ocean_profile_type),
intent(inout) :: profile
1842 profile%wod_cast_num=0
1843 profile%fix_depth=0.
1844 profile%ocn_vehicle=0.
1845 profile%database_id=0.
1847 profile%profile_flag=-1
1848 profile%profile_flag_s=-1
1851 profile%accepted=.false.
1853 if (
ASSOCIATED(profile%next)) profile%next=>null()
1854 if (
ASSOCIATED(profile%depth)) profile%depth=>null()
1855 if (
ASSOCIATED(profile%data_t)) profile%data_t=>null()
1856 if (
ASSOCIATED(profile%data_s)) profile%data_s=>null()
1857 if (
ASSOCIATED(profile%flag_t)) profile%flag_t=>null()
1858 if (
ASSOCIATED(profile%flag_s)) profile%flag_s=>null()
1859 profile%temp_err=0.0
1860 profile%salt_err=0.0
1861 if (
ASSOCIATED(profile%ms_t)) profile%ms_t=>null()
1862 if (
ASSOCIATED(profile%ms_s)) profile%ms_s=>null()
1866 if (
ASSOCIATED(profile%model_time)) profile%model_time=>null()
1867 if (
ASSOCIATED(profile%model_grid)) profile%model_grid=>null()
1868 if (
ASSOCIATED(profile%k_index)) profile%k_index=>null()
1869 profile%i_index=-1.0
1870 profile%j_index=-1.0
integer, parameter, private sfc_file
subroutine, public get_date(time, year, month, day, hour, minute, second, tick, err_msg)
subroutine nullify_obs_prof(profile)
subroutine backward_obs_profile(Obs, model_t, model_s)
real, private min_obs_err_t
type(ocean_profile_type), dimension(:), allocatable, target, save, private profiles
subroutine create_ideal_profiles(localize)
subroutine copy_obs_sfc(Obs_in, Obs_out)
integer, save, private iec
subroutine adjust_obs_error_sfc(Diff)
real, dimension(:), allocatable x_grid
subroutine mult_obs_i_mse_profile(Obs)
type(time_type), dimension(0:100), public time_window
integer, save, private isd
subroutine add_tidal_error(Prof)
subroutine backward_obs_sfc(Obs, model)
integer, save, private nk
subroutine adjust_obs_error_profile(Prof)
integer, save, private jed
integer, parameter, public model_ocean
subroutine, public get_obs(model_time, Prof, Sfc, nprof, nsfc)
subroutine, public get_field_info(n, fld_type, fld_name, model, num_methods)
integer, save, private num_sfc_obs
real, private eta_tide_const
subroutine, public oda_core_init(Domain, Grid, localize)
integer, parameter, public max_links
Maximum number of records per profile for storage for profiles.
type(time_type) function, public get_cal_time(time_increment, units, calendar, permit_calendar_conversion)
real, parameter, private depth_max
integer function, public check_nml_error(IOSTAT, NML_NAME)
real, parameter, private salt_min
real, private min_obs_err_s
character(len=input_str_length), dimension(:), allocatable, target, public input_nml_file
real, parameter, private temp_min
subroutine assign_forward_model_profile(Obs1, Obs2)
real, save, private max_prof_spacing
integer, save, private jeg
type(ocean_surface_type), dimension(:), allocatable, target, save, private sfc_obs
real, parameter, public radian
Equal to RAD_TO_DEG for backward compatability. [rad/deg].
integer, save, private num_profiles
subroutine diff_obs_sfc(prof1, prof2, Diff)
subroutine forward_obs_sfc(Sfc, Guess, Diff)
subroutine, public write_ocean_data_init()
real, parameter, private temp_max
real, dimension(:), allocatable y_grid
integer, save, private jsg
type(grid_type), pointer grd
integer, save, private isg
subroutine assign_forward_model_sfc(Obs1, Obs2)
integer, save, private ied
real, parameter, public missing_value
integer, save, private isc
integer, save, private jsc
real function, public frac_index(value, array)
subroutine copy_obs_prof(obs_in, obs_out)
subroutine diff_obs_profile(prof1, prof2, Diff)
real, save, private min_prof_depth
real, dimension(:,:,:), allocatable, save, private sum_wgt
subroutine init_observations(localize)
integer, save, private jec
integer, parameter, private idealized_profiles
real, parameter, private depth_min
integer, parameter, private profile_file
subroutine, public get_time(Time, seconds, days, ticks, err_msg)
integer, dimension(:), allocatable nprof_in_comp_domain
subroutine, public purge_obs()
subroutine, public get_field_methods(n, methods)
subroutine, public open_profile_dataset(filename, localize)
integer, save, private ieg
integer, save, private jsd
character(len=len(cs)) function lowercase(cs)
Derived type containing the data.
subroutine forward_obs_profile(Model_obs, fg_t, fg_s)
subroutine mult_obs_i_mse_sfc(a, Obs)
logical add_tidal_aliasing
real, parameter, private salt_max
real(fp), parameter, public pi
integer, parameter, private max_files