Skip to content

Commit

Permalink
Reconcile several differences between the mpi and serial drivers. Not…
Browse files Browse the repository at this point in the history
…e that the changes is this commit might change the behavior of the code.
  • Loading branch information
micaeljtoliveira committed Jan 6, 2025
1 parent d3ad94b commit abadde1
Show file tree
Hide file tree
Showing 2 changed files with 49 additions and 31 deletions.
76 changes: 46 additions & 30 deletions src/offline/cable_mpimaster.F90
Original file line number Diff line number Diff line change
Expand Up @@ -89,8 +89,10 @@ MODULE cable_mpimaster
renameFiles, &
LUCdriver
USE cable_mpicommon
USE cable_IO_vars_module, ONLY : NO_CHECK
USE casa_cable
USE casa_inout_module
USE cable_checks_module, ONLY: constant_check_range

IMPLICIT NONE

Expand Down Expand Up @@ -359,9 +361,12 @@ SUBROUTINE mpidrv_master (comm, trunk_sumbal, dels, koffset, kend, PLUME, CRU)
CALL open_met_file( dels, koffset, kend, spinup, CTFRZ )

CASE ('plum')
! PLUME experiment setup using WATCH
IF ( .NOT. PLUME%LeapYears ) LOY = 365
kend = NINT(24.0*3600.0/dels) * LOY

CASE ('cru')
! TRENDY experiment using CRU-NCEP
LOY = 365
kend = NINT(24.0*3600.0/dels) * LOY

Expand All @@ -370,6 +375,9 @@ SUBROUTINE mpidrv_master (comm, trunk_sumbal, dels, koffset, kend, PLUME, CRU)
WRITE(*,*) 'Looking for global offline run info.'
CALL open_met_file( dels, koffset, kend, spinup, CTFRZ )

CASE ('site')
STOP 'MetType "site" can only be used in serial'

CASE DEFAULT
IF ( globalMetfile%l_gpcc ) THEN
ncciy = CurYear
Expand Down Expand Up @@ -402,9 +410,34 @@ SUBROUTINE mpidrv_master (comm, trunk_sumbal, dels, koffset, kend, PLUME, CRU)
casamet, casabal, phen, POP, spinup, &
CEMSOIL, CTFRZ, LUC_EXPT, POPLUC )

IF (check%ranges /= NO_CHECK) THEN
WRITE (*, *) "Checking parameter ranges"
CALL constant_check_range(soil, veg, 0, met)
END IF

IF (CABLE_USER%POPLUC .AND. TRIM(CABLE_USER%POPLUC_RunType) .EQ. 'static') &
CABLE_USER%POPLUC= .FALSE.

! Open output file:
IF (.NOT.CASAONLY) THEN
IF ( TRIM(filename%out) .EQ. '' ) THEN
IF ( CABLE_USER%YEARSTART .GT. 0 ) THEN
WRITE( dum, FMT="(I4,'_',I4)")CABLE_USER%YEARSTART, &
CABLE_USER%YEAREND
filename%out = TRIM(filename%path)//'/'//&
TRIM(cable_user%RunIden)//'_'//&
TRIM(dum)//'_cable_out.nc'
ELSE
filename%out = TRIM(filename%path)//'/'//&
TRIM(cable_user%RunIden)//'_cable_out.nc'
ENDIF
ENDIF
IF (YYYY.EQ.CABLE_USER%YEARSTART) THEN
CALL nullify_write() ! nullify pointers
CALL open_output_file( dels, soil, veg, bgc, rough, met)
ENDIF
ENDIF

ssnow%otss_0 = ssnow%tgg(:,1)
ssnow%otss = ssnow%tgg(:,1)
ssnow%tss = ssnow%tgg(:,1)
Expand Down Expand Up @@ -525,28 +558,6 @@ SUBROUTINE mpidrv_master (comm, trunk_sumbal, dels, koffset, kend, PLUME, CRU)
! MPI: mostly original serial code follows...
ENDIF ! CALL1


! Open output file:
IF (.NOT.CASAONLY) THEN
IF ( TRIM(filename%out) .EQ. '' ) THEN
IF ( CABLE_USER%YEARSTART .GT. 0 ) THEN
WRITE( dum, FMT="(I4,'_',I4)")CABLE_USER%YEARSTART, &
CABLE_USER%YEAREND
filename%out = TRIM(filename%path)//'/'//&
TRIM(cable_user%RunIden)//'_'//&
TRIM(dum)//'_cable_out.nc'
ELSE
filename%out = TRIM(filename%path)//'/'//&
TRIM(cable_user%RunIden)//'_cable_out.nc'
ENDIF
ENDIF
IF (YYYY.EQ.CABLE_USER%YEARSTART) THEN
CALL nullify_write() ! nullify pointers
CALL open_output_file( dels, soil, veg, bgc, rough, met)
ENDIF
ENDIF


! globally (WRT code) accessible kend through USE cable_common_module
ktau_gl = 0
kwidth_gl = INT(dels)
Expand Down Expand Up @@ -576,6 +587,9 @@ SUBROUTINE mpidrv_master (comm, trunk_sumbal, dels, koffset, kend, PLUME, CRU)
CALL CRU_GET_SUBDIURNAL_MET(CRU, imet, YYYY, 1, kend, &
(YYYY.EQ.CABLE_USER%YearEnd))

CASE ('site')
STOP 'MetType "site" can only be used in serial'

CASE DEFAULT
CALL get_met_data( spinup, spinConv, imet, soil, &
rad, iveg, kend, dels, CTFRZ, iktau+koffset, &
Expand Down Expand Up @@ -1134,6 +1148,13 @@ SUBROUTINE mpidrv_master (comm, trunk_sumbal, dels, koffset, kend, PLUME, CRU)

END DO SPINLOOP

IF ( SpinConv .AND. .NOT. CASAONLY) THEN
! Close output file and deallocate main variables:
CALL close_output_file( bal, air, bgc, canopy, met, &
rad, rough, soil, ssnow, &
sum_flux, veg )
ENDIF

IF (icycle > 0 .AND. (.NOT.spincasa).AND. (.NOT.casaonly)) THEN
! MPI: gather casa results from all the workers

Expand Down Expand Up @@ -1236,10 +1257,13 @@ SUBROUTINE mpidrv_master (comm, trunk_sumbal, dels, koffset, kend, PLUME, CRU)

call create_new_gridinfo(filename%type,filename%gridnew,mlon,mlat,landmask,patchfrac_new)

print *, 'writing casapools: land use'
call WRITE_LANDUSE_CASA_RESTART_NC(cend(mland), lucmp, CASAONLY )

print *, 'writing cable restart: land use'
call create_landuse_cable_restart(logn, dels, ktau, soil, cend(mland),lucmp,cstart,cend,nap, met)

print *, 'deallocating'
call landuse_deallocate_mp(cend(mland),ms,msn,nrb,mplant,mlitter,msoil,mwood,lucmp)
ENDIF

Expand All @@ -1250,14 +1274,6 @@ SUBROUTINE mpidrv_master (comm, trunk_sumbal, dels, koffset, kend, PLUME, CRU)
TRIM(cable_user%MetType) .NE. "gswp3" .AND. &
TRIM(cable_user%MetType) .NE. "plum" .AND. &
TRIM(cable_user%MetType) .NE. "cru") CALL close_met_file
IF (.NOT. CASAONLY) THEN
! Close output file and deallocate main variables:
CALL close_output_file( bal, air, bgc, canopy, met, &
rad, rough, soil, ssnow, &
sum_flux, veg )

! WRITE(logn,*) bal%wbal_tot, bal%ebal_tot, bal%ebal_tot_cncheck
ENDIF

! Close log file
CLOSE(logn)
Expand Down
4 changes: 3 additions & 1 deletion src/offline/cable_serial.F90
Original file line number Diff line number Diff line change
Expand Up @@ -275,6 +275,7 @@ SUBROUTINE serialdrv(trunk_sumbal, NRRRR, dels, koffset, kend, GSWP_MID, PLUME,


! outer loop - spinup loop no. ktau_tot :
ktau = 0
SPINLOOP:DO WHILE ( SPINon )

NREP: DO RRRR = 1, NRRRR
Expand All @@ -290,7 +291,7 @@ SUBROUTINE serialdrv(trunk_sumbal, NRRRR, dels, koffset, kend, GSWP_MID, PLUME,
IF ( leaps ) THEN
calendar = "standard"
END IF
IF ( IS_LEAPYEAR( YYYY ) ) THEN
IF ( leaps .AND. IS_LEAPYEAR( YYYY ) ) THEN
LOY = 366
END IF

Expand Down Expand Up @@ -392,6 +393,7 @@ SUBROUTINE serialdrv(trunk_sumbal, NRRRR, dels, koffset, kend, GSWP_MID, PLUME,

IF ( CABLE_USER%POPLUC .AND. TRIM(CABLE_USER%POPLUC_RunType) .EQ. 'static') &
CABLE_USER%POPLUC= .FALSE.

! Open output file:
IF (.NOT.CASAONLY) THEN
IF ( TRIM(filename%out) .EQ. '' ) THEN
Expand Down

0 comments on commit abadde1

Please sign in to comment.