Skip to content
2 changes: 1 addition & 1 deletion documentation/docs/user_guide/inputs/cable_nml.md
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,7 @@ The cable.nml file includes some settings that are common across all CABLE appli
| cable_user%soil_thermal_fix | logical | .TRUE. .FALSE. | .FALSE. | Use alternative soil conductivity implementation. |
| cable_user%phenology_switch | character(len=20) | 'MODIS' 'climate' | 'MODIS' | Use prescribed MODIS phenology or climate dependant phenology. |
| cable_user%RunIden | character(len=10) | any string of max. 10 characters | 'STANDARD' | Run identifier string for input/output files. |
| cable_user%MetType | character(len=6) | '' 'gswp' 'gswp3' 'plum' 'cru' 'site' 'bios' | ' ' | Type of input meteorological data. |
| cable_user%MetType | character(len=6) | '' 'gswp' 'gswp3' 'plum' 'cru' 'site' 'bios' 'prin' | ' ' | Type of input meteorological data. |
| cable_user%soil_struc | character(len=20) | 'default' 'sli' | 'default' | Use default or soil-litter-iso soil model. |
| cable_user%POP_out | character(len=3) | 'epi' 'rst' 'ini' | 'rst' | POP restart file type. `'epi'` is end of year state `'rst'` is a standard restart file, `'ini'` is an initialisation restart file. |
| cable_user%POP_rst | character(len=50) | any string of max. 50 characters | ' ' | POP restart file directory. |
Expand Down
48 changes: 44 additions & 4 deletions src/offline/cable_driver_common.F90
Original file line number Diff line number Diff line change
Expand Up @@ -108,6 +108,7 @@ MODULE cable_driver_common_mod
PUBLIC :: cable_driver_init_default
PUBLIC :: prepareFiles
PUBLIC :: renameFiles
PUBLIC :: prepareFiles_princeton
PUBLIC :: LUCdriver
PUBLIC :: compare_consistency_check_values

Expand Down Expand Up @@ -325,10 +326,9 @@ SUBROUTINE cable_driver_init_cru(dels, koffset, CRU)
END SUBROUTINE cable_driver_init_cru

SUBROUTINE prepareFiles(ncciy)
!* Select the correct files given the year for filenames following the gswp format
!* Select the correct files given the year for filenames following
! the gswp format

USE cable_IO_vars_module, ONLY: logn,gswpfile
IMPLICIT NONE
INTEGER, INTENT(IN) :: ncciy !! Year to select met. forcing data.

WRITE(logn,*) 'CABLE offline global run using gswp forcing for ', ncciy
Expand All @@ -346,7 +346,8 @@ SUBROUTINE prepareFiles(ncciy)
END SUBROUTINE prepareFiles

SUBROUTINE renameFiles(logn,inFile,ncciy,inName)
!! Replace the year in the filename with the value of ncciy.
!* Replace the year in the filename with the value of ncciy
! for the gswp file format.

IMPLICIT NONE
INTEGER, INTENT(IN) :: logn !! Log file unit number
Expand All @@ -363,6 +364,45 @@ SUBROUTINE renameFiles(logn,inFile,ncciy,inName)

END SUBROUTINE renameFiles

SUBROUTINE prepareFiles_princeton(ncciy)
!* Select the correct files given the year for filenames following the
! princeton format
INTEGER, INTENT(IN) :: ncciy

WRITE(logn,*) 'CABLE offline global run using princeton forcing for ', ncciy
PRINT *, 'CABLE offline global run using princeton forcing for ', ncciy

CALL renameFiles_princeton(logn,gswpfile%rainf,ncciy,'rainf')
CALL renameFiles_princeton(logn,gswpfile%LWdown,ncciy,'LWdown')
CALL renameFiles_princeton(logn,gswpfile%SWdown,ncciy,'SWdown')
CALL renameFiles_princeton(logn,gswpfile%PSurf,ncciy,'PSurf')
CALL renameFiles_princeton(logn,gswpfile%Qair,ncciy,'Qair')
CALL renameFiles_princeton(logn,gswpfile%Tair,ncciy,'Tair')
CALL renameFiles_princeton(logn,gswpfile%wind,ncciy,'wind')

END SUBROUTINE prepareFiles_princeton

SUBROUTINE renameFiles_princeton(logn,inFile,ncciy,inName)
!* Replace the year in the filename with the value of ncciy for
! the princeton format
INTEGER, INTENT(IN) :: logn,ncciy
INTEGER:: nn
CHARACTER(LEN=200), INTENT(INOUT) :: inFile
CHARACTER(LEN=*), INTENT(IN) :: inName
INTEGER :: idummy

nn = INDEX(inFile,'19')
READ(inFile(nn:nn+3),'(i4)') idummy
WRITE(inFile(nn:nn+3),'(i4.4)') ncciy
nn = INDEX(inFile,'19', BACK=.TRUE.)
READ(inFile(nn:nn+3),'(i4)') idummy
WRITE(inFile(nn:nn+3),'(i4.4)') ncciy
READ(inFile(nn-5:nn-2),'(i4)') idummy
WRITE(inFile(nn-5:nn-2),'(i4.4)') ncciy
WRITE(logn,*) TRIM(inName), ' global data from ', TRIM(inFile)

END SUBROUTINE renameFiles_princeton

!==============================================================================
! subroutine for
SUBROUTINE LUCdriver( casabiome,casapool, &
Expand Down
57 changes: 39 additions & 18 deletions src/offline/cable_input.F90
Original file line number Diff line number Diff line change
Expand Up @@ -400,7 +400,7 @@ SUBROUTINE open_met_file(dels,koffset,kend,spinup, TFRZ)
PRINT*,'rainf'
CALL handle_err( ok )
ENDIF
IF(.NOT. globalMetfile%l_gpcc) THEN
IF(.NOT. globalMetfile%l_gpcc .AND. cable_user%MetType .NE. "prin") THEN
ok = NF90_OPEN(gswpfile%snowf,0,ncid_snow)
IF (ok /= NF90_NOERR) THEN
PRINT*,'snow'
Expand Down Expand Up @@ -497,9 +497,12 @@ SUBROUTINE open_met_file(dels,koffset,kend,spinup, TFRZ)
IF(ok/=NF90_NOERR) THEN ! if failed
! Try 'lon' instead of x
ok = NF90_INQ_DIMID(ncid_met,'lon', xdimID)
IF(ok/=NF90_NOERR) CALL nc_abort &
(ok,'Error finding x dimension in '&
//TRIM(filename%met)//' (SUBROUTINE open_met_file)')
IF(ok/=NF90_NOERR) THEN ! MMY
ok = NF90_INQ_DIMID(ncid_met,'longitude', xdimID) ! MMY ! For princeton
IF(ok/=NF90_NOERR) CALL nc_abort & ! MMY
(ok,'Error finding x dimension in '& ! MMY
//TRIM(filename%met)//' (SUBROUTINE open_met_file)') ! MMY
END IF ! MMY
END IF
ok = NF90_INQUIRE_DIMENSION(ncid_met,xdimID,len=xdimsize)
IF(ok/=NF90_NOERR) CALL nc_abort &
Expand All @@ -510,9 +513,12 @@ SUBROUTINE open_met_file(dels,koffset,kend,spinup, TFRZ)
IF(ok/=NF90_NOERR) THEN ! if failed
! Try 'lat' instead of y
ok = NF90_INQ_DIMID(ncid_met,'lat', ydimID)
IF(ok/=NF90_NOERR) CALL nc_abort &
(ok,'Error finding y dimension in ' &
//TRIM(filename%met)//' (SUBROUTINE open_met_file)')
IF(ok/=NF90_NOERR) THEN ! MMY
ok = NF90_INQ_DIMID(ncid_met,'latitude', ydimID) ! MMY ! For princeton
IF(ok/=NF90_NOERR) CALL nc_abort & ! MMY
(ok,'Error finding y dimension in ' & ! MMY
//TRIM(filename%met)//' (SUBROUTINE open_met_file)') ! MMY
END IF ! MMY
END IF
ok = NF90_INQUIRE_DIMENSION(ncid_met,ydimID,len=ydimsize)
IF(ok/=NF90_NOERR) CALL nc_abort &
Expand Down Expand Up @@ -821,7 +827,10 @@ SUBROUTINE open_met_file(dels,koffset,kend,spinup, TFRZ)
!===== done bug fixing for timevar in PALS met file ===============

!===== gswp input file has bug in timeunits ===========
IF (ncciy > 0) WRITE(timeunits(26:27),'(i2.2)') 0
IF (TRIM(cable_user%MetType) .NE. "prin") THEN ! MMY
IF (ncciy > 0) WRITE(timeunits(26:27),'(i2.2)') 0
END IF ! MMY

!===== done bug fixing for timeunits in gwsp file ========
WRITE(logn,*) 'Time variable units: ', timeunits
! Get coordinate field:
Expand All @@ -848,17 +857,25 @@ SUBROUTINE open_met_file(dels,koffset,kend,spinup, TFRZ)
! start time) from character to integer; calculate starting hour-of-day,
! day-of-year, year:
IF (.NOT.cable_user%GSWP3) THEN
READ(timeunits(15:18),*) syear
READ(timeunits(20:21),*) smoy ! integer month
READ(timeunits(23:24),*) sdoytmp ! integer day of that month
READ(timeunits(26:27),*) shod ! starting hour of day
IF (cable_user%MetType .eq. "prin") THEN ! MMY
READ(timeunits(13:16),*) syear ! MMY
READ(timeunits(18:19),*) smoy ! integer month ! MMY
READ(timeunits(21:22),*) sdoytmp ! integer day of that month ! MMY
READ(timeunits(24:25),*) shod ! starting hour of day ! MMY
ELSE ! MMY
READ(timeunits(15:18),*) syear
READ(timeunits(20:21),*) smoy ! integer month
READ(timeunits(23:24),*) sdoytmp ! integer day of that month
READ(timeunits(26:27),*) shod ! starting hour of day
END IF
ELSE
syear=ncciy
smoy=1
sdoytmp=1
shod=0
END IF


! if site data, shift start time to middle of timestep
! only do this if not already at middle of timestep
! vh_js !
Expand Down Expand Up @@ -1055,14 +1072,18 @@ SUBROUTINE open_met_file(dels,koffset,kend,spinup, TFRZ)
IF(ok /= NF90_NOERR) CALL nc_abort &
(ok,'Error finding Rainf units in met data file ' &
//TRIM(filename%met)//' (SUBROUTINE open_met_file)')
IF(metunits%Rainf(1:8)=='kg/m^2/s'.OR.metunits%Rainf(1:6)=='kg/m2s'.OR.metunits%Rainf(1:10)== &
'kgm^-2s^-1'.OR.metunits%Rainf(1:4)=='mm/s'.OR. &
metunits%Rainf(1:6)=='mms^-1'.OR. &
metunits%Rainf(1:7)=='kg/m^2s'.OR.metunits%Rainf(1:10)=='kg m-2 s-1'.OR.metunits%Wind(1:5)/='m s-1') THEN
IF(metunits%Rainf(1:8)=='kg/m^2/s' .OR. &
metunits%Rainf(1:7)=='kg/m2/s' .OR. &
metunits%Rainf(1:6)=='kg/m2s' .OR. &
metunits%Rainf(1:10)=='kgm^-2s^-1' .OR. &
metunits%Rainf(1:4)=='mm/s' .OR. &
metunits%Rainf(1:6)=='mms^-1' .OR. &
metunits%Rainf(1:7)=='kg/m^2s' .OR. &
metunits%Rainf(1:10)=='kg m-2 s-1' ) THEN
! Change from mm/s to mm/time step:
convert%Rainf = dels
ELSE IF(metunits%Rainf(1:4)=='mm/h'.OR.metunits%Rainf(1:6)== &
'mmh^-1') THEN
ELSE IF(metunits%Rainf(1:4)=='mm/h' .OR. &
metunits%Rainf(1:6)== 'mmh^-1' ) THEN
! Change from mm/h to mm/time step:
convert%Rainf = dels/3600.0
ELSE
Expand Down
17 changes: 12 additions & 5 deletions src/offline/cable_mpimaster.F90
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ MODULE cable_mpimaster
delgwM, &
LALLOC, &
prepareFiles, &
renameFiles, &
prepareFiles_princeton, &
LUCdriver, &
compare_consistency_check_values
USE cable_mpicommon
Expand Down Expand Up @@ -352,11 +352,17 @@ SUBROUTINE mpidrv_master (comm, dels, koffset, kend, PLUME, CRU)
ENDIF

SELECT CASE (TRIM(cable_user%MetType))
CASE ('gswp')
CASE ('gswp', 'prin')
ncciy = CurYear

WRITE(*,*) 'Looking for global offline run info.'
CALL prepareFiles(ncciy)

IF ( TRIM(cable_user%MetType) == 'gswp' ) THEN
CALL prepareFiles(ncciy)
ELSE ! cable_user%MetType == 'prin'
CALL prepareFiles_princeton(ncciy)
END IF

CALL open_met_file( dels, koffset, kend, spinup, CTFRZ )

CASE ('plum')
Expand Down Expand Up @@ -739,7 +745,8 @@ SUBROUTINE mpidrv_master (comm, dels, koffset, kend, PLUME, CRU)

END SELECT
IF ( (TRIM(cable_user%MetType) .NE. 'gswp') .AND. &
(TRIM(cable_user%MetType) .NE. 'gswp3') ) CurYear = met%year(1)
(TRIM(cable_user%MetType) .NE. 'gswp3') .AND. &
(TRIM(cable_user%MetType) .NE. 'prin' )) CurYear = met%year(1)

!$ IF ( CASAONLY .AND. IS_CASA_TIME("dread", yyyy, iktau, kstart, koffset, &
!$ kend, ktauday, logn) ) THEN
Expand Down Expand Up @@ -846,7 +853,7 @@ SUBROUTINE mpidrv_master (comm, dels, koffset, kend, PLUME, CRU)
IF ( (.NOT. CASAONLY).AND. spinConv ) THEN

SELECT CASE (TRIM(cable_user%MetType))
CASE ('plum', 'cru', 'gswp', 'gswp3')
CASE ('plum', 'cru', 'gswp', 'gswp3', 'prin')
CALL write_output( dels, ktau_tot, met, canopy, casaflux, casapool, &
casamet,ssnow, &
rad, bal, air, soil, veg, CSBOLTZ, &
Expand Down
2 changes: 2 additions & 0 deletions src/offline/cable_offline_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,8 @@ PROGRAM cable_offline_driver
CALL cable_driver_init_gswp(mpi_grp, GSWP_MID, NRRRR)
CASE('gswp3')
CALL cable_driver_init_gswp(mpi_grp)
CASE('prin')
CALL cable_driver_init_gswp(mpi_grp, GSWP_MID, NRRRR)
CASE('plum')
CALL cable_driver_init_plume(dels, koffset, PLUME)
CASE('cru')
Expand Down
11 changes: 8 additions & 3 deletions src/offline/cable_serial.F90
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,7 @@ MODULE cable_serial
delgwM, &
LALLOC, &
prepareFiles, &
renameFiles, &
prepareFiles_princeton, &
LUCdriver, &
compare_consistency_check_values
USE cable_def_types_mod
Expand Down Expand Up @@ -296,10 +296,15 @@ SUBROUTINE serialdrv(NRRRR, dels, koffset, kend, GSWP_MID, PLUME, CRU, site)

! Check for gswp run
SELECT CASE (TRIM(cable_user%MetType))
CASE ('gswp')
CASE ('gswp', 'prin')
ncciy = CurYear

CALL prepareFiles(ncciy)
IF (cable_user%MetType == 'gswp') THEN
CALL prepareFiles(ncciy)
ELSE ! cable_user%MetType == 'prin'
CALL prepareFiles_princeton(ncciy) ! MMY
END IF

IF ( RRRR .EQ. 1 ) THEN
CALL open_met_file( dels, koffset, kend, spinup, CTFRZ )
IF (leaps.AND.is_leapyear(YYYY).AND.kend.EQ.2920) THEN
Expand Down
Loading