next up previous contents
Next: lnd_run_mct Up: Fortran: Module Interface lnd_comp_mct Previous: Fortran: Module Interface lnd_comp_mct   Contents

lnd_init_mct


INTERFACE:

   subroutine lnd_init_mct( EClock, cdata_l, x2l_l, l2x_l, &
                                    cdata_r, r2x_r,        &
                                    cdata_s, x2s_s, s2x_s, &
                                    NLFilename )
DESCRIPTION:

Initialize land surface model and obtain relevant atmospheric model arrays back from (i.e. albedos, surface temperature and snow cover over land).


USES:

     use shr_kind_mod     , only : r8 => shr_kind_r8
     use clm_time_manager , only : get_nstep, get_step_size, set_timemgr_init, &
                                   set_nextsw_cday
     use clm_atmlnd       , only : clm_mapl2a, clm_l2a, atm_l2a
     use clm_comp         , only : clm_init0, clm_init1, clm_init2
     use clm_varctl       , only : finidat,single_column, set_clmvarctl
     use controlMod       , only : control_setNL
     use domainMod        , only : adomain
     use clm_varpar       , only : rtmlon, rtmlat
     use clm_varorb       , only : eccen, obliqr, lambm0, mvelpp
     use abortutils       , only : endrun
     use clm_varctl       , only : iulog, noland
     use shr_file_mod     , only : shr_file_setLogUnit, shr_file_setLogLevel, &
                                   shr_file_getLogUnit, shr_file_getLogLevel, &
                                   shr_file_getUnit, shr_file_setIO
     use seq_cdata_mod    , only : seq_cdata, seq_cdata_setptrs
     use spmdMod          , only : masterproc, spmd_init
     use seq_timemgr_mod  , only : seq_timemgr_EClockGetData
     use seq_infodata_mod , only : seq_infodata_type, seq_infodata_GetData, seq_infodata_PutData, &
                                   seq_infodata_start_type_start, seq_infodata_start_type_cont,   &
                                   seq_infodata_start_type_brnch
     use mct_mod          , only : mct_aVect, mct_gsMap, mct_gGrid, mct_aVect_init, mct_aVect_zero
     use seq_flds_mod
     use seq_flds_indices
     use ESMF_mod
     implicit none
ARGUMENTS:
     type(ESMF_Clock),             intent(in)    :: EClock           ! Input synchronization clock
     type(seq_cdata),              intent(inout) :: cdata_l          ! Input land-model driver data
     type(mct_aVect),              intent(inout) :: x2l_l, l2x_l     ! land model import and export states
     type(seq_cdata),              intent(inout) :: cdata_r          ! Input runoff-model driver data
     type(mct_aVect),              intent(inout) :: r2x_r            ! River export state
     type(seq_cdata),  optional,   intent(inout) :: cdata_s          ! Input snow-model (land-ice) driver data
     type(mct_aVect),  optional,   intent(inout) :: x2s_s, s2x_s     ! Snow-model import and export states
     character(len=*), optional,   intent(in)    :: NLFilename       ! Namelist filename to read
LOCAL VARIABLES:
     integer                          :: LNDID	     ! Land identifyer
     integer                          :: mpicom_lnd   ! MPI communicator
     type(mct_gsMap),         pointer :: GSMap_lnd    ! Land model MCT GS map
     type(mct_gGrid),         pointer :: dom_l        ! Land model domain
     type(mct_gsMap),         pointer :: GSMap_rof    ! Runoff model MCT GS map
     type(mct_gGrid),         pointer :: dom_r        ! Runoff model domain
     type(seq_infodata_type), pointer :: infodata     ! CCSM driver level info data
     integer  :: lsize                                ! size of attribute vector
     integer  :: i,j                                  ! indices
     integer  :: dtime_sync                           ! coupling time-step from the input synchronization clode
     integer  :: dtime_clm                            ! clm time-step
     logical  :: exists                               ! true if file exists
     real(r8) :: scmlat                               ! single-column latitude
     real(r8) :: scmlon                               ! single-column longitude
     real(r8) :: nextsw_cday                          ! calday from clock of next radiation computation
     character(len=SHR_KIND_CL) :: caseid             ! case identifier name
     character(len=SHR_KIND_CL) :: ctitle             ! case description title
     character(len=SHR_KIND_CL) :: starttype          ! start-type (startup, continue, branch, hybrid)
     character(len=SHR_KIND_CL) :: calendar           ! calendar type name
     character(len=SHR_KIND_CL) :: hostname           ! hostname of machine running on
     character(len=SHR_KIND_CL) :: version            ! Model version
     character(len=SHR_KIND_CL) :: username           ! user running the model
     integer :: nsrest                                ! clm restart type
     integer :: perpetual_ymd                         ! perpetual date
     integer :: ref_ymd                               ! reference date (YYYYMMDD)
     integer :: ref_tod                               ! reference time of day (sec)
     integer :: start_ymd                             ! start date (YYYYMMDD)
     integer :: start_tod                             ! start time of day (sec)
     integer :: stop_ymd                              ! stop date (YYYYMMDD)
     integer :: stop_tod                              ! stop time of day (sec)
     logical :: brnch_retain_casename                 ! flag if should retain the case name on a branch start type
     logical :: perpetual_run                         ! flag if should cycle over a perpetual date or not
     integer :: lbnum                                 ! input to memory diagnostic
     integer :: shrlogunit,shrloglev                  ! old values for log unit and log level
     character(len=32), parameter :: sub = 'lnd_init_mct'
     character(len=*),  parameter :: format = "('("//trim(sub)//") :',A)"
REVISION HISTORY:
   Author: Mariana Vertenstein



Erik Kluzek 2010-06-21