Skip to content

Commit 8f7480d

Browse files
committed
Merge branch 'master' into stages-2025
2 parents 2a62033 + b893dc9 commit 8f7480d

File tree

8 files changed

+180
-119
lines changed

8 files changed

+180
-119
lines changed

bldsva/intf_DA/pdaf/framework/init_dim_obs_f_pdaf.F90

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -459,7 +459,7 @@ SUBROUTINE init_dim_obs_f_pdaf(step, dim_obs_f)
459459
! Switch for how to check index of CLM observations
460460
! True: Use snapping distance between long/lat on CLM grid
461461
! False: Use index arrays from `domain_def_clm`
462-
is_use_dr = .false.
462+
is_use_dr = .true.
463463

464464
if(model .eq. tag_model_clm) then
465465

@@ -514,7 +514,7 @@ SUBROUTINE init_dim_obs_f_pdaf(step, dim_obs_f)
514514
! Dimension of full observation vector
515515
! ------------------------------------
516516

517-
! add and broadcast size of local observation dimensions using mpi_allreduce
517+
! add and broadcast size of PE-local observation dimensions using mpi_allreduce
518518
call mpi_allreduce(dim_obs_p, sum_dim_obs_p, 1, MPI_INTEGER, MPI_SUM, &
519519
comm_filter, ierror)
520520

@@ -524,20 +524,20 @@ SUBROUTINE init_dim_obs_f_pdaf(step, dim_obs_f)
524524
! Check sum of dimensions of PE-local observation vectors against
525525
! dimension of full observation vector
526526
if (.not. sum_dim_obs_p == dim_obs) then
527-
print *, "TSMP-PDAF mype(w)=", mype_world, ": ERROR Sum of local observation dimensions"
527+
print *, "TSMP-PDAF mype(w)=", mype_world, ": ERROR Sum of PE-local observation dimensions"
528528
print *, "sum_dim_obs_p=", sum_dim_obs_p
529529
print *, "dim_obs=", dim_obs
530530
call abort_parallel()
531531
end if
532532

533-
! Gather local observation dimensions and displacements in arrays
533+
! Gather PE-local observation dimensions and displacements in arrays
534534
! ----------------------------------------------------------------
535535

536-
! Allocate array of local observation dimensions
536+
! Allocate array of PE-local observation dimensions
537537
IF (ALLOCATED(local_dims_obs)) DEALLOCATE(local_dims_obs)
538538
ALLOCATE(local_dims_obs(npes_filter))
539539

540-
! Gather array of local observation dimensions
540+
! Gather array of PE-local observation dimensions
541541
call mpi_allgather(dim_obs_p, 1, MPI_INTEGER, local_dims_obs, 1, MPI_INTEGER, &
542542
comm_filter, ierror)
543543

bldsva/intf_DA/pdaf/framework/init_dim_obs_pdaf.F90

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -510,27 +510,27 @@ SUBROUTINE init_dim_obs_pdaf(step, dim_obs_p)
510510
! Dimension of full observation vector
511511
! ------------------------------------
512512

513-
! add and broadcast size of local observation dimensions using mpi_allreduce
513+
! add and broadcast size of PE-local observation dimensions using mpi_allreduce
514514
call mpi_allreduce(dim_obs_p, sum_dim_obs_p, 1, MPI_INTEGER, MPI_SUM, &
515515
comm_filter, ierror)
516516

517517
! Check sum of dimensions of PE-local observation vectors against
518518
! dimension of full observation vector
519519
if (.not. sum_dim_obs_p == dim_obs) then
520-
print *, "TSMP-PDAF mype(w)=", mype_world, ": ERROR Sum of local observation dimensions"
520+
print *, "TSMP-PDAF mype(w)=", mype_world, ": ERROR Sum of PE-local observation dimensions"
521521
print *, "sum_dim_obs_p=", sum_dim_obs_p
522522
print *, "dim_obs=", dim_obs
523523
call abort_parallel()
524524
end if
525525

526-
! Gather local observation dimensions and displacements in arrays
526+
! Gather PE-local observation dimensions and displacements in arrays
527527
! ----------------------------------------------------------------
528528

529-
! Allocate array of local observation dimensions
529+
! Allocate array of PE-local observation dimensions
530530
IF (ALLOCATED(local_dims_obs)) DEALLOCATE(local_dims_obs)
531531
ALLOCATE(local_dims_obs(npes_filter))
532532

533-
! Gather array of local observation dimensions
533+
! Gather array of PE-local observation dimensions
534534
call mpi_allgather(dim_obs_p, 1, MPI_INTEGER, local_dims_obs, 1, MPI_INTEGER, &
535535
comm_filter, ierror)
536536

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

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -152,7 +152,7 @@ subroutine define_clm_statevec(mype)
152152

153153
! Set `clm_varsize`, even though it is currently not used
154154
! for `clmupdate_swc.eq.1`
155-
clm_varsize = clm_statevecsize
155+
clm_varsize = cc
156156
clm_statevecsize = cc
157157

158158
IF (allocated(state_pdaf2clm_c_p)) deallocate(state_pdaf2clm_c_p)
@@ -243,14 +243,13 @@ subroutine define_clm_statevec(mype)
243243
if (g .eq. j) then
244244
if (newgridcell) then
245245
newgridcell = .false.
246+
cc = cc + 1
246247
! Possibliy: Add state_pdaf2clm_g_p
247248
state_pdaf2clm_c_p(cc) = jj
248249
state_pdaf2clm_j_p(cc) = i
249250
end if
250251
end if
251252
end do
252-
253-
cc = cc + 1
254253
end do
255254
end do
256255

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

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -58,8 +58,8 @@ subroutine print_update_clm(ts,ttot) bind(C,name="print_update_clm")
5858
real(r8), pointer :: psand(:,:)
5959
real(r8), pointer :: pclay(:,:)
6060
real(r8), pointer :: porgm(:,:)
61-
real(r8), pointer :: clmstate_tmp_local(:)
62-
real(r8), pointer :: clmstate_tmp_global(:)
61+
! real(r8), pointer :: clmstate_tmp_local(:)
62+
! real(r8), pointer :: clmstate_tmp_global(:)
6363
real(r8), allocatable :: clmstate_out(:,:,:)
6464
integer ,dimension(4) :: dimids
6565
integer ,dimension(1) :: il_var_id
@@ -71,13 +71,13 @@ subroutine print_update_clm(ts,ttot) bind(C,name="print_update_clm")
7171

7272
call get_proc_global(ng=numg,nl=numl,nc=numc,np=nump)
7373
call get_proc_bounds(begg,endg,begl,endl,begc,endc,begp,endp)
74-
allocate(clmstate_tmp_local(nlevsoi*(-begc+endc)), stat=nerror)
74+
! allocate(clmstate_tmp_local(nlevsoi*(-begc+endc)), stat=nerror)
7575

7676
ndlon = ldomain%ni
7777
ndlat = ldomain%nj
7878

7979
if (masterproc) then
80-
allocate(clmstate_tmp_global(nlevsoi*numg), stat=nerror)
80+
! allocate(clmstate_tmp_global(nlevsoi*numg), stat=nerror)
8181
allocate(clmstate_out(ndlon,ndlat,nlevsoi), stat=nerror)
8282
end if
8383

@@ -203,10 +203,10 @@ subroutine print_update_clm(ts,ttot) bind(C,name="print_update_clm")
203203
if(masterproc) then
204204
status = nf90_close(il_file_id)
205205
deallocate(clmstate_out)
206-
deallocate(clmstate_tmp_global)
206+
! deallocate(clmstate_tmp_global)
207207
end if
208208

209-
deallocate(clmstate_tmp_local)
209+
! deallocate(clmstate_tmp_local)
210210

211211
end subroutine print_update_clm
212212
#endif

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

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -152,7 +152,7 @@ subroutine define_clm_statevec(mype)
152152

153153
! Set `clm_varsize`, even though it is currently not used
154154
! for `clmupdate_swc.eq.1`
155-
clm_varsize = clm_statevecsize
155+
clm_varsize = cc
156156
clm_statevecsize = cc
157157

158158
IF (allocated(state_pdaf2clm_c_p)) deallocate(state_pdaf2clm_c_p)
@@ -243,14 +243,13 @@ subroutine define_clm_statevec(mype)
243243
if (g .eq. j) then
244244
if (newgridcell) then
245245
newgridcell = .false.
246+
cc = cc + 1
246247
! Possibliy: Add state_pdaf2clm_g_p
247248
state_pdaf2clm_c_p(cc) = jj
248249
state_pdaf2clm_j_p(cc) = i
249250
end if
250251
end if
251252
end do
252-
253-
cc = cc + 1
254253
end do
255254
end do
256255

bldsva/intf_DA/pdaf/model/eclm/print_update_clm_5.F90

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -58,8 +58,8 @@ subroutine print_update_clm(ts,ttot) bind(C,name="print_update_clm")
5858
real(r8), pointer :: psand(:,:)
5959
real(r8), pointer :: pclay(:,:)
6060
real(r8), pointer :: porgm(:,:)
61-
real(r8), pointer :: clmstate_tmp_local(:)
62-
real(r8), pointer :: clmstate_tmp_global(:)
61+
! real(r8), pointer :: clmstate_tmp_local(:)
62+
! real(r8), pointer :: clmstate_tmp_global(:)
6363
real(r8), allocatable :: clmstate_out(:,:,:)
6464
integer ,dimension(4) :: dimids
6565
integer ,dimension(1) :: il_var_id
@@ -71,13 +71,13 @@ subroutine print_update_clm(ts,ttot) bind(C,name="print_update_clm")
7171

7272
call get_proc_global(ng=numg,nl=numl,nc=numc,np=nump)
7373
call get_proc_bounds(begg,endg,begl,endl,begc,endc,begp,endp)
74-
allocate(clmstate_tmp_local(nlevsoi*(-begc+endc)), stat=nerror)
74+
! allocate(clmstate_tmp_local(nlevsoi*(-begc+endc)), stat=nerror)
7575

7676
ndlon = ldomain%ni
7777
ndlat = ldomain%nj
7878

7979
if (masterproc) then
80-
allocate(clmstate_tmp_global(nlevsoi*numg), stat=nerror)
80+
! allocate(clmstate_tmp_global(nlevsoi*numg), stat=nerror)
8181
allocate(clmstate_out(ndlon,ndlat,nlevsoi), stat=nerror)
8282
end if
8383

@@ -203,10 +203,10 @@ subroutine print_update_clm(ts,ttot) bind(C,name="print_update_clm")
203203
if(masterproc) then
204204
status = nf90_close(il_file_id)
205205
deallocate(clmstate_out)
206-
deallocate(clmstate_tmp_global)
206+
! deallocate(clmstate_tmp_global)
207207
end if
208208

209-
deallocate(clmstate_tmp_local)
209+
! deallocate(clmstate_tmp_local)
210210

211211
end subroutine print_update_clm
212212
#endif

bldsva/intf_DA/pdaf/model/wrapper_tsmp.c

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -200,7 +200,9 @@ void update_tsmp(){
200200
#if defined CLMSA
201201
if((model == tag_model_clm) && ((clmupdate_swc != 0) || (clmupdate_T != 0))){
202202
update_clm(&tstartcycle, &mype_world);
203-
print_update_clm(&tcycle, &total_steps);
203+
if(clmprint_swc == 1 || clmupdate_texture == 1 || clmupdate_texture == 2){
204+
print_update_clm(&tcycle, &total_steps);
205+
}
204206
}
205207
#endif
206208

0 commit comments

Comments
 (0)