Skip to content

Commit

Permalink
Merge branch 'CoLM-SYSU:master' into master
Browse files Browse the repository at this point in the history
  • Loading branch information
zhangsp8 authored Jan 26, 2024
2 parents 05c8705 + 1b37767 commit ee688fe
Show file tree
Hide file tree
Showing 29 changed files with 6,554 additions and 6,507 deletions.
2 changes: 1 addition & 1 deletion main/CoLM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -504,7 +504,7 @@ PROGRAM CoLM
time_used = (end_time - start_time) / c_per_sec
IF (time_used >= 3600) THEN
write(*,101) time_used/3600, mod(time_used,3600)/60, mod(time_used,60)
elseif (time_used >= 60) THEN
ELSEIF (time_used >= 60) THEN
write(*,102) time_used/60, mod(time_used,60)
ELSE
write(*,103) time_used
Expand Down
84 changes: 42 additions & 42 deletions main/LULCC/MOD_Lulcc_Driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,8 @@ MODULE MOD_Lulcc_Driver



SUBROUTINE LulccDriver (casename,dir_landdata,dir_restart,&
idate,greenwich)
SUBROUTINE LulccDriver (casename,dir_landdata,dir_restart,&
idate,greenwich)

! ======================================================================
! !PURPOSE:
Expand Down Expand Up @@ -54,61 +54,61 @@ SUBROUTINE LulccDriver (casename,dir_landdata,dir_restart,&
logical, intent(in) :: greenwich !true: greenwich time, false: local time
integer, intent(inout) :: idate(3) !year, julian day, seconds of the starting time

! allocate Lulcc memory
CALL allocate_LulccTimeInvariants
CALL allocate_LulccTimeVariables
! allocate Lulcc memory
CALL allocate_LulccTimeInvariants
CALL allocate_LulccTimeVariables

! SAVE variables
CALL SAVE_LulccTimeInvariants
CALL SAVE_LulccTimeVariables
! SAVE variables
CALL SAVE_LulccTimeInvariants
CALL SAVE_LulccTimeVariables

! =============================================================
! cold start for Lulcc
! =============================================================
! =============================================================
! cold start for Lulcc
! =============================================================

IF (p_is_master) THEN
print *, ">>> LULCC: initializing..."
ENDIF
IF (p_is_master) THEN
print *, ">>> LULCC: initializing..."
ENDIF

CALL LulccInitialize (casename,dir_landdata,dir_restart,&
idate,greenwich)
CALL LulccInitialize (casename,dir_landdata,dir_restart,&
idate,greenwich)


! =============================================================
! simple method for variable recovery
! =============================================================
! =============================================================
! simple method for variable recovery
! =============================================================

IF (DEF_LULCC_SCHEME == 1) THEN
IF (p_is_master) THEN
print *, ">>> LULCC: simple method for variable recovery..."
IF (DEF_LULCC_SCHEME == 1) THEN
IF (p_is_master) THEN
print *, ">>> LULCC: simple method for variable recovery..."
ENDIF
CALL REST_LulccTimeVariables
ENDIF
CALL REST_LulccTimeVariables
ENDIF


! =============================================================
! conserved method for variable revocery
! =============================================================
! =============================================================
! conserved method for variable revocery
! =============================================================

IF (DEF_LULCC_SCHEME == 2) THEN
IF (p_is_master) THEN
print *, ">>> LULCC: Mass&Energy conserve for variable recovery..."
IF (DEF_LULCC_SCHEME == 2) THEN
IF (p_is_master) THEN
print *, ">>> LULCC: Mass&Energy conserve for variable recovery..."
ENDIF
CALL allocate_LulccTransferTrace()
CALL REST_LulccTimeVariables
CALL MAKE_LulccTransferTrace(idate(1))
CALL LulccMassEnergyConserve()
ENDIF
CALL allocate_LulccTransferTrace()
CALL REST_LulccTimeVariables
CALL MAKE_LulccTransferTrace(idate(1))
CALL LulccMassEnergyConserve()
ENDIF


! deallocate Lulcc memory
CALL deallocate_LulccTimeInvariants()
CALL deallocate_LulccTimeVariables()
IF (DEF_LULCC_SCHEME == 2) THEN
CALL deallocate_LulccTransferTrace()
ENDIF
! deallocate Lulcc memory
CALL deallocate_LulccTimeInvariants()
CALL deallocate_LulccTimeVariables()
IF (DEF_LULCC_SCHEME == 2) THEN
CALL deallocate_LulccTransferTrace()
ENDIF

END SUBROUTINE LulccDriver
END SUBROUTINE LulccDriver

END MODULE MOD_Lulcc_Driver
#endif
Expand Down
106 changes: 53 additions & 53 deletions main/LULCC/MOD_Lulcc_Initialize.F90
Original file line number Diff line number Diff line change
Expand Up @@ -11,11 +11,11 @@ MODULE MOD_Lulcc_Initialize
PUBLIC :: LulccInitialize

!-----------------------------------------------------------------------
CONTAINS
CONTAINS
!-----------------------------------------------------------------------

SUBROUTINE LulccInitialize (casename,dir_landdata,dir_restart,&
idate,greenwich)
SUBROUTINE LulccInitialize (casename,dir_landdata,dir_restart,&
idate,greenwich)

! ======================================================================
!
Expand Down Expand Up @@ -65,89 +65,89 @@ SUBROUTINE LulccInitialize (casename,dir_landdata,dir_restart,&
integer :: year, jday
! ----------------------------------------------------------------------

! initial time of model run
! ............................
CALL adj2begin(idate)
! initial time of model run
! ............................
CALL adj2begin(idate)

year = idate(1)
jday = idate(2)
year = idate(1)
jday = idate(2)

CALL Init_GlobalVars
CAll Init_LC_Const
CAll Init_PFT_Const
CALL Init_GlobalVars
CAll Init_LC_Const
CAll Init_PFT_Const

! deallocate pixelset and mesh data of previous year
CALL mesh_free_mem
CALL landelm%forc_free_mem
CALL landpatch%forc_free_mem
! deallocate pixelset and mesh data of previous year
CALL mesh_free_mem
CALL landelm%forc_free_mem
CALL landpatch%forc_free_mem
#if (defined LULC_IGBP_PFT || defined LULC_IGBP_PC)
CALL landpft%forc_free_mem
CALL landpft%forc_free_mem
#endif
#ifdef URBAN_MODEL
CALL landurban%forc_free_mem
CALL landurban%forc_free_mem
#endif

! load pixelset and mesh data of next year
! CALL pixel%load_from_file (dir_landdata)
! CALL gblock%load_from_file (dir_landdata)
CALL mesh_load_from_file (dir_landdata, year)
CALL pixelset_load_from_file (dir_landdata, 'landelm' , landelm , numelm , year)
! load pixelset and mesh data of next year
! CALL pixel%load_from_file (dir_landdata)
! CALL gblock%load_from_file (dir_landdata)
CALL mesh_load_from_file (dir_landdata, year)
CALL pixelset_load_from_file (dir_landdata, 'landelm' , landelm , numelm , year)

! load CATCHMENT of next year
! load CATCHMENT of next year
#ifdef CATCHMENT
CALL pixelset_load_from_file (dir_landdata, 'landhru' , landhru , numhru , year)
CALL pixelset_load_from_file (dir_landdata, 'landhru' , landhru , numhru , year)
#endif

! load landpatch data of next year
CALL pixelset_load_from_file (dir_landdata, 'landpatch', landpatch, numpatch, year)
! load landpatch data of next year
CALL pixelset_load_from_file (dir_landdata, 'landpatch', landpatch, numpatch, year)

! load pft data of PFT/PC of next year
! load pft data of PFT/PC of next year
#if (defined LULC_IGBP_PFT || defined LULC_IGBP_PC)
CALL pixelset_load_from_file (dir_landdata, 'landpft' , landpft , numpft , year)
CALL map_patch_to_pft
CALL pixelset_load_from_file (dir_landdata, 'landpft' , landpft , numpft , year)
CALL map_patch_to_pft
#endif

! load urban data of next year
! load urban data of next year
#ifdef URBAN_MODEL
CALL pixelset_load_from_file (dir_landdata, 'landurban', landurban, numurban, year)
CALL map_patch_to_urban
CALL pixelset_load_from_file (dir_landdata, 'landurban', landurban, numurban, year)
CALL map_patch_to_urban
#endif

! initialize for data associated with land element
! initialize for data associated with land element
#if (defined UNSTRUCTURED || defined CATCHMENT)
CALL elm_vector_init ()
CALL elm_vector_init ()
#ifdef CATCHMENT
CALL hru_vector_init ()
CALL hru_vector_init ()
#endif
#endif

! build element subfraction of next year which it's needed in the MOD_Lulcc_TransferTrace
IF (p_is_worker) THEN
CALL elm_patch%build (landelm, landpatch, use_frac = .true.)
ENDIF
! build element subfraction of next year which it's needed in the MOD_Lulcc_TransferTrace
IF (p_is_worker) THEN
CALL elm_patch%build (landelm, landpatch, use_frac = .true.)
ENDIF

! initialize for SrfdataDiag, it is needed in the MOD_Lulcc_TransferTrace for outputing transfer_matrix
! initialize for SrfdataDiag, it is needed in the MOD_Lulcc_TransferTrace for outputing transfer_matrix
#ifdef SrfdataDiag
#ifdef GRIDBASED
CALL init_gridbased_mesh_grid ()
CALL gdiag%define_by_copy (gridmesh)
CALL init_gridbased_mesh_grid ()
CALL gdiag%define_by_copy (gridmesh)
#else
CALL gdiag%define_by_ndims(3600,1800)
CALL gdiag%define_by_ndims(3600,1800)
#endif
CALL srfdata_diag_init (dir_landdata)
CALL srfdata_diag_init (dir_landdata)
#endif

! --------------------------------------------------------------------
! Deallocates memory for CoLM 1d [numpatch] variables
! --------------------------------------------------------------------
CALL deallocate_TimeInvariants
CALL deallocate_TimeVariables
! --------------------------------------------------------------------
! Deallocates memory for CoLM 1d [numpatch] variables
! --------------------------------------------------------------------
CALL deallocate_TimeInvariants
CALL deallocate_TimeVariables

! initialize all state variables of next year
CALL initialize (casename,dir_landdata,dir_restart,&
idate,year,greenwich,lulcc_call=.true.)
! initialize all state variables of next year
CALL initialize (casename,dir_landdata,dir_restart,&
idate,year,greenwich,lulcc_call=.true.)

END SUBROUTINE LulccInitialize
END SUBROUTINE LulccInitialize

END MODULE MOD_Lulcc_Initialize
#endif
Expand Down
Loading

0 comments on commit ee688fe

Please sign in to comment.