Skip to content

Commit f55671f

Browse files
authored
PDAF: Soil moisture state vector with gridcell averages (#268)
* CLM:statevec_colmean - introduce hydrologically active grid cells only - save prior column means in `clm_statevec_orig`, used for computing update increment - update column values with increment-factor from mean * define_clm_statevec: re-arranging state-vector definition * Bugfix: remove loop-name `col` Error message: ``` eclm/enkf_clm_mod_5.F90(264): error #6401: The attributes of this name conflict with those made accessible by a USE statement. [COL] ```
1 parent 73b9012 commit f55671f

File tree

6 files changed

+398
-197
lines changed

6 files changed

+398
-197
lines changed

bldsva/intf_DA/pdaf/framework/init_dim_obs_pdaf.F90

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -959,7 +959,16 @@ SUBROUTINE init_dim_obs_pdaf(step, dim_obs_p)
959959
end if
960960
#endif
961961
else
962-
obs_index_p(cnt) = g-begg+1 + ((endg-begg+1) * (clmobs_layer(i)-1))
962+
#ifdef CLMFIVE
963+
if(clmstatevec_only_active.eq.1) then
964+
obs_index_p(cnt) = state_clm2pdaf_p(c,clmobs_layer(i))
965+
else
966+
967+
#endif
968+
obs_index_p(cnt) = g-begg+1 + ((endg-begg+1) * (clmobs_layer(i)-1))
969+
#ifdef CLMFIVE
970+
end if
971+
#endif
963972
end if
964973

965974
!write(*,*) 'obs_index_p(',cnt,') is',obs_index_p(cnt)

bldsva/intf_DA/pdaf/model/clm5_0/enkf_clm_mod_5.F90

Lines changed: 178 additions & 96 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,7 @@ module enkf_clm_mod
4141
integer :: clm_begc,clm_endc
4242
integer :: clm_begp,clm_endp
4343
real(r8),allocatable :: clm_statevec(:)
44+
real(r8),allocatable :: clm_statevec_orig(:)
4445
integer,allocatable :: state_pdaf2clm_c_p(:)
4546
integer,allocatable :: state_pdaf2clm_j_p(:)
4647
! clm_paramarr: Contains LAI used in obs_op_pdaf for computing model
@@ -54,6 +55,7 @@ module enkf_clm_mod
5455
#endif
5556
integer(c_int),bind(C,name="clmprint_et") :: clmprint_et
5657
integer(c_int),bind(C,name="clmstatevec_allcol") :: clmstatevec_allcol
58+
integer(c_int),bind(C,name="clmstatevec_colmean") :: clmstatevec_colmean
5759
integer(c_int),bind(C,name="clmstatevec_only_active") :: clmstatevec_only_active
5860
integer(c_int),bind(C,name="clmstatevec_max_layer") :: clmstatevec_max_layer
5961
integer(c_int),bind(C,name="clmt_printensemble") :: clmt_printensemble
@@ -98,6 +100,7 @@ subroutine define_clm_statevec(mype)
98100
integer :: jj
99101
integer :: c
100102
integer :: g
103+
integer :: cg
101104
integer :: cc
102105
integer :: cccheck
103106

@@ -122,140 +125,160 @@ subroutine define_clm_statevec(mype)
122125
clm_begp = begp
123126
clm_endp = endp
124127

128+
! Soil Moisture DA: State vector index arrays
125129
if(clmupdate_swc.eq.1) then
130+
131+
! 1) COL/GRC: CLM->PDAF
132+
IF (allocated(state_clm2pdaf_p)) deallocate(state_clm2pdaf_p)
133+
allocate(state_clm2pdaf_p(begc:endc,nlevsoi))
134+
do i=1,nlevsoi
135+
do c=clm_begc,clm_endc
136+
! Default: inactive
137+
state_clm2pdaf_p = ispval
138+
end do
139+
end do
140+
141+
! All column variables in state vector
126142
if(clmstatevec_allcol.eq.1) then
127143

144+
! Only hydrologically active columns
128145
if(clmstatevec_only_active .eq. 1) then
129146

130-
IF (allocated(state_clm2pdaf_p)) deallocate(state_clm2pdaf_p)
131-
allocate(state_clm2pdaf_p(begc:endc,nlevsoi))
132-
133147
cc = 0
134148

135149
do i=1,nlevsoi
136-
do c=clm_begc,clm_endc
137-
! Only take into account layers above input maximum layer
138-
if(i<=clmstatevec_max_layer) then
150+
! Only take into account layers above input maximum layer
151+
if(i<=clmstatevec_max_layer) then
152+
153+
do c=clm_begc,clm_endc
139154
! Only take into account hydrologically active columns
140155
! and layers above bedrock
141156
if(col%hydrologically_active(c) .and. i<=col%nbedrock(c)) then
142157
cc = cc + 1
143158
state_clm2pdaf_p(c,i) = cc
144-
else
145-
state_clm2pdaf_p(c,i) = ispval
146159
end if
147-
else
148-
state_clm2pdaf_p(c,i) = ispval
149-
end if
150-
end do
151-
end do
160+
end do
152161

153-
! Set `clm_varsize`, even though it is currently not used
154-
! for `clmupdate_swc.eq.1`
155-
clm_varsize = cc
156-
clm_statevecsize = cc
157-
158-
IF (allocated(state_pdaf2clm_c_p)) deallocate(state_pdaf2clm_c_p)
159-
allocate(state_pdaf2clm_c_p(clm_statevecsize))
160-
IF (allocated(state_pdaf2clm_j_p)) deallocate(state_pdaf2clm_j_p)
161-
allocate(state_pdaf2clm_j_p(clm_statevecsize))
162-
163-
cc = 0
164-
165-
do i=1,nlevsoi
166-
do c=clm_begc,clm_endc
167-
! Only take into account layers above input maximum layer
168-
if(i<=clmstatevec_max_layer) then
169-
! Only take into account hydrologically active columns
170-
! and layers above bedrock
171-
if(col%hydrologically_active(c) .and. i<=col%nbedrock(c)) then
172-
cc = cc + 1
173-
state_pdaf2clm_c_p(cc) = c
174-
state_pdaf2clm_j_p(cc) = i
175-
end if
176-
end if
177-
end do
162+
end if
178163
end do
179164

165+
! All column variables in state vector simplifying the indexing
180166
else
181167

182-
IF (allocated(state_clm2pdaf_p)) deallocate(state_clm2pdaf_p)
183-
allocate(state_clm2pdaf_p(begc:endc,nlevsoi))
184-
185168
do i=1,nlevsoi
186169
do c=clm_begc,clm_endc
187170
state_clm2pdaf_p(c,i) = (c - clm_begc + 1) + (i - 1)*(clm_endc - clm_begc + 1)
188171
end do
189172
end do
190173

191-
! #cols values per grid-cell
192-
clm_varsize = (endc-begc+1) * nlevsoi
193-
clm_statevecsize = (endc-begc+1) * nlevsoi
174+
end if
194175

195-
IF (allocated(state_pdaf2clm_c_p)) deallocate(state_pdaf2clm_c_p)
196-
allocate(state_pdaf2clm_c_p(clm_statevecsize))
197-
IF (allocated(state_pdaf2clm_j_p)) deallocate(state_pdaf2clm_j_p)
198-
allocate(state_pdaf2clm_j_p(clm_statevecsize))
176+
! Gridcell values or averages in state vector
177+
else
178+
179+
! Only hydrologically active columns
180+
if(clmstatevec_only_active.eq.1) then
199181

200182
cc = 0
201183

184+
do i=1,nlevsoi
185+
! Only layers above max_layer
186+
if(i<=clmstatevec_max_layer) then
187+
188+
do g=clm_begg,clm_endg
189+
190+
newgridcell = .true.
191+
192+
do c=clm_begc,clm_endc
193+
if(col%gridcell(c) == g) then
194+
! All hydrologically active columns above
195+
! bedrock in a gridcell point to the state
196+
! vector index of the gridcell
197+
if(col%hydrologically_active(c) .and. i<=col%nbedrock(c)) then
198+
if(newgridcell) then
199+
! Update the index if first col found for grc,
200+
! otherwise reproduce previous index
201+
cc = cc + 1
202+
newgridcell = .false.
203+
end if
204+
state_clm2pdaf_p(c,i) = cc
205+
end if
206+
end if
207+
end do
208+
209+
end do
210+
end if
211+
end do
212+
else
202213
do i=1,nlevsoi
203214
do c=clm_begc,clm_endc
204-
cc = cc + 1
205-
state_pdaf2clm_c_p(cc) = c
206-
state_pdaf2clm_j_p(cc) = i
215+
! All columns in a gridcell are assigned the updated
216+
! gridcell-SWC
217+
state_clm2pdaf_p(c,i) = (col%gridcell(c) - clm_begg + 1) + (i - 1)*(clm_endg - clm_begg + 1)
207218
end do
208219
end do
209-
210220
end if
211221

212-
else
213-
214-
IF (allocated(state_clm2pdaf_p)) deallocate(state_clm2pdaf_p)
215-
allocate(state_clm2pdaf_p(begc:endc,nlevsoi))
222+
end if
216223

217-
do i=1,nlevsoi
218-
do c=clm_begc,clm_endc
219-
! All columns in a gridcell are assigned the updated
220-
! gridcell-SWC
221-
state_clm2pdaf_p(c,i) = (col%gridcell(c) - clm_begg + 1) + (i - 1)*(clm_endg - clm_begg + 1)
222-
end do
223-
end do
224+
! 2) COL/GRC: STATEVECSIZE
225+
if(clmstatevec_only_active.eq.1) then
226+
! Use iterator cc for setting state vector size.
227+
!
228+
! Set `clm_varsize`, even though it is currently not used
229+
! for `clmupdate_swc.eq.1`
230+
clm_varsize = cc
231+
clm_statevecsize = cc
232+
else
233+
if(clmstatevec_allcol.eq.1) then
234+
! #cols * #levels
235+
clm_varsize = (endc-begc+1) * nlevsoi
236+
clm_statevecsize = (endc-begc+1) * nlevsoi
237+
else
238+
! #grcs * #levels
239+
clm_varsize = (endg-begg+1) * nlevsoi
240+
clm_statevecsize = (endg-begg+1) * nlevsoi
241+
end if
242+
end if
224243

225-
! One value per grid-cell
226-
clm_varsize = (endg-begg+1) * nlevsoi
227-
clm_statevecsize = (endg-begg+1) * nlevsoi
244+
! 3) COL/GRC: PDAF->CLM
245+
IF (allocated(state_pdaf2clm_c_p)) deallocate(state_pdaf2clm_c_p)
246+
allocate(state_pdaf2clm_c_p(clm_statevecsize))
247+
IF (allocated(state_pdaf2clm_j_p)) deallocate(state_pdaf2clm_j_p)
248+
allocate(state_pdaf2clm_j_p(clm_statevecsize))
228249

229-
IF (allocated(state_pdaf2clm_c_p)) deallocate(state_pdaf2clm_c_p)
230-
allocate(state_pdaf2clm_c_p(clm_statevecsize))
231-
IF (allocated(state_pdaf2clm_j_p)) deallocate(state_pdaf2clm_j_p)
232-
allocate(state_pdaf2clm_j_p(clm_statevecsize))
250+
! Defaults
251+
do cc=1,clm_statevecsize
252+
state_pdaf2clm_c_p(cc) = ispval
253+
state_pdaf2clm_j_p(cc) = ispval
254+
end do
233255

234-
cc = 0
256+
do cc=1,clm_statevecsize
235257

236-
do i=1,nlevsoi
237-
do j=clm_begg,clm_endg
238-
239-
! SWC from the first column of each gridcell
240-
newgridcell = .true.
241-
do jj=clm_begc,clm_endc
242-
g = col%gridcell(jj)
243-
if (g .eq. j) then
244-
if (newgridcell) then
245-
newgridcell = .false.
246-
cc = cc + 1
247-
! Possibliy: Add state_pdaf2clm_g_p
248-
state_pdaf2clm_c_p(cc) = jj
249-
state_pdaf2clm_j_p(cc) = i
250-
end if
251-
end if
252-
end do
258+
lay: do i=1,nlevsoi
259+
do c=clm_begc,clm_endc
260+
if (state_clm2pdaf_p(c,i) == cc) then
261+
! Set column index and then exit loop
262+
state_pdaf2clm_c_p(cc) = c
263+
state_pdaf2clm_j_p(cc) = i
264+
exit lay
265+
end if
253266
end do
254-
end do
255-
267+
end do lay
256268

269+
#ifdef PDAF_DEBUG
270+
! Check that all state vectors have been assigned c, i
271+
if(state_pdaf2clm_c_p(cc) == ispval) then
272+
write(*,*) 'cc: ', cc
273+
error stop "state_pdaf2clm_c_p not set at cc"
274+
end if
275+
if(state_pdaf2clm_j_p(cc) == ispval) then
276+
write(*,*) 'cc: ', cc
277+
error stop "state_pdaf2clm_j_p not set at cc"
278+
end if
279+
#endif
280+
end do
257281

258-
end if
259282
endif
260283

261284
if(clmupdate_swc.eq.2) then
@@ -288,6 +311,14 @@ subroutine define_clm_statevec(mype)
288311
allocate(clm_statevec(clm_statevecsize))
289312
end if
290313

314+
! Allocate statevector-duplicate for saving original column mean
315+
! values used in computing increments during updating the state
316+
! vector in column-mean-mode.
317+
IF (allocated(clm_statevec_orig)) deallocate(clm_statevec_orig)
318+
if (clmupdate_swc.ne.0 .and. clmstatevec_colmean.ne.0) then
319+
allocate(clm_statevec_orig(clm_statevecsize))
320+
end if
321+
291322
!write(*,*) 'clm_paramsize is ',clm_paramsize
292323
if (allocated(clm_paramarr)) deallocate(clm_paramarr) !hcp
293324
if ((clmupdate_T.ne.0)) then !hcp
@@ -322,7 +353,8 @@ subroutine set_clm_statevec(tstartcycle, mype)
322353
real(r8), pointer :: psand(:,:)
323354
real(r8), pointer :: pclay(:,:)
324355
real(r8), pointer :: porgm(:,:)
325-
integer :: i,j,jj,g,cc=0,offset=0
356+
integer :: i,j,jj,g,c,cc=0,offset=0
357+
integer :: n_c
326358
character (len = 34) :: fn !TSMP-PDAF: function name for state vector output
327359
character (len = 34) :: fn2 !TSMP-PDAF: function name for swc output
328360

@@ -352,9 +384,51 @@ subroutine set_clm_statevec(tstartcycle, mype)
352384

353385
if(clmupdate_swc.ne.0) then
354386
! write swc values to state vector
355-
do cc = 1, clm_statevecsize
356-
clm_statevec(cc) = swc(state_pdaf2clm_c_p(cc), state_pdaf2clm_j_p(cc))
357-
end do
387+
if (clmstatevec_colmean.eq.1) then
388+
389+
do cc = 1, clm_statevecsize
390+
391+
clm_statevec(cc) = 0.0
392+
n_c = 0
393+
394+
! Get gridcell and layer
395+
g = col%gridcell(state_pdaf2clm_c_p(cc))
396+
j = state_pdaf2clm_j_p(cc)
397+
398+
! Loop over all columns
399+
do c=clm_begc,clm_endc
400+
! Select columns in gridcell g
401+
if(col%gridcell(c).eq.g) then
402+
! Select hydrologically active columns
403+
if(col%hydrologically_active(c)) then
404+
! Add active column to swc-sum
405+
clm_statevec(cc) = clm_statevec(cc) + swc(c,j)
406+
n_c = n_c + 1
407+
end if
408+
end if
409+
end do
410+
411+
if(n_c == 0) then
412+
write(*,*) "WARNING: Gridcell g=", g
413+
write(*,*) "WARNING: Layer j=", j
414+
write(*,*) "Grid cell g at layer j without hydrologically active column! Setting SWC as in gridcell mode."
415+
clm_statevec(cc) = swc(state_pdaf2clm_c_p(cc), state_pdaf2clm_j_p(cc))
416+
else
417+
! Normalize sum to average
418+
clm_statevec(cc) = clm_statevec(cc) / real(n_c, r8)
419+
end if
420+
421+
! Save prior column mean state vector for computing
422+
! increment in updating the state vector
423+
clm_statevec_orig(cc) = clm_statevec(cc)
424+
425+
end do
426+
427+
else
428+
do cc = 1, clm_statevecsize
429+
clm_statevec(cc) = swc(state_pdaf2clm_c_p(cc), state_pdaf2clm_j_p(cc))
430+
end do
431+
end if
358432
endif
359433

360434
!hcp LAI
@@ -534,7 +608,15 @@ subroutine update_clm(tstartcycle, mype) bind(C,name="update_clm")
534608
!h2osoi_vol(c,j) = h2osoi_liq(c,j)/(dz(c,j)*denh2o) + h2osoi_ice(c,j)/(dz(c,j)*denice)
535609
end if
536610

537-
swc_update = clm_statevec(state_clm2pdaf_p(j,i))
611+
if (clmstatevec_colmean.eq.1) then
612+
! Update SWC column value with the increment-factor
613+
! of the state vector update (state vector updates
614+
! are means of cols in grc)
615+
swc_update = swc(j,i) * clm_statevec(state_clm2pdaf_p(j,i)) / clm_statevec_orig(state_clm2pdaf_p(j,i))
616+
else
617+
! Update SWC with updated state vector
618+
swc_update = clm_statevec(state_clm2pdaf_p(j,i))
619+
end if
538620

539621
if(swc_update.le.watmin_check) then
540622
swc(j,i) = watmin_set

bldsva/intf_DA/pdaf/model/common/enkf.h

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -90,6 +90,7 @@ GLOBAL int clmupdate_texture;
9090
GLOBAL int clmprint_swc;
9191
GLOBAL int clmprint_et;
9292
GLOBAL int clmstatevec_allcol;
93+
GLOBAL int clmstatevec_colmean;
9394
GLOBAL int clmstatevec_only_active;
9495
GLOBAL int clmstatevec_max_layer;
9596
GLOBAL int clmt_printensemble;

0 commit comments

Comments
 (0)